| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
RIO.Prelude.Lens
- view :: MonadReader s m => Getting a s a -> m a
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- type ASetter' s a = ASetter s s a a
- type Getting r s a = (a -> Const * r a) -> s -> Const * r s
- type Lens s t a b = forall (f :: * -> *). Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type SimpleGetter s a = forall r. Getting r s a
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- over :: ASetter s t a b -> (a -> b) -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- sets :: ((a -> b) -> s -> t) -> ASetter s t a b
- to :: (s -> a) -> SimpleGetter s a
- (^.) :: s -> Getting a s a -> a
Documentation
view :: MonadReader s m => Getting a s a -> m a Source #
type ASetter s t a b = (a -> Identity b) -> s -> Identity t #
ASetter s t a b is something that turns a function modifying a value into a function modifying a structure. If you ignore Identity (as Identity a is the same thing as a), the type is:
type ASetter s t a b = (a -> b) -> s -> t
The reason Identity is used here is for ASetter to be composable with other types, such as Lens.
Technically, if you're writing a library, you shouldn't use this type for setters you are exporting from your library; the right type to use is Setter, but it is not provided by this package (because then it'd have to depend on distributive). It's completely alright, however, to export functions which take an ASetter as an argument.
type Getting r s a = (a -> Const * r a) -> s -> Const * r s #
Functions that operate on getters and folds – such as (^.), (^..), (^?) – use Getter r s a (with different values of r) to describe what kind of result they need. For instance, (^.) needs the getter to be able to return a single value, and so it accepts a getter of type Getting a s a. (^..) wants the getter to gather values together, so it uses Getting (Endo [a]) s a (it could've used Getting [a] s a instead, but it's faster with Endo). The choice of r depends on what you want to do with elements you're extracting from s.
type Lens s t a b = forall (f :: * -> *). Functor f => (a -> f b) -> s -> f t #
Lens s t a b is the lowest common denominator of a setter and a getter, something that has the power of both; it has a Functor constraint, and since both Const and Identity are functors, it can be used whenever a getter or a setter is needed.
ais the type of the value inside of structurebis the type of the replaced valuesis the type of the whole structuretis the type of the structure after replacingain it withb
type Lens' s a = Lens s s a a #
This is a type alias for monomorphic lenses which don't change the type of the container (or of the value inside).
type SimpleGetter s a = forall r. Getting r s a #
A SimpleGetter s a extracts a from s; so, it's the same thing as (s -> a), but you can use it in lens chains because its type looks like this:
type SimpleGetter s a = forall r. (a -> Const r a) -> s -> Const r s
Since Const r is a functor, SimpleGetter has the same shape as other lens types and can be composed with them. To get (s -> a) out of a SimpleGetter, choose r ~ a and feed Const :: a -> Const a a to the getter:
-- the actual signature is more permissive: --view::Gettinga s a -> s -> aview::SimpleGetters a -> s -> aviewgetter =getConst. getterConst
The actual Getter from lens is more general:
type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
I'm not currently aware of any functions that take lens's Getter but won't accept SimpleGetter, but you should try to avoid exporting SimpleGetters anyway to minimise confusion. Alternatively, look at microlens-contra, which provides a fully lens-compatible Getter.
Lens users: you can convert a SimpleGetter to Getter by applying to . view to it.
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b #
lens creates a Lens from a getter and a setter. The resulting lens isn't the most effective one (because of having to traverse the structure twice when modifying), but it shouldn't matter much.
A (partial) lens for list indexing:
ix :: Int ->Lens'[a] a ix i =lens(!!i) -- getter (\s b -> take i s ++ b : drop (i+1) s) -- setter
Usage:
>>> [1..9]^.ix 3 4 >>> [1..9] & ix 3%~negate [1,2,3,-4,5,6,7,8,9]
When getting, the setter is completely unused; when setting, the getter is unused. Both are used only when the value is being modified. For instance, here we define a lens for the 1st element of a list, but instead of a legitimate getter we use undefined. Then we use the resulting lens for setting and it works, which proves that the getter wasn't used:
>>>[1,2,3] & lens undefined (\s b -> b : tail s) .~ 10[10,2,3]
over :: ASetter s t a b -> (a -> b) -> s -> t #
Getting fmap in a roundabout way:
overmapped::Functorf => (a -> b) -> f a -> f bovermapped=fmap
Applying a function to both components of a pair:
overboth:: (a -> b) -> (a, a) -> (b, b)overboth= \f t -> (f (fst t), f (snd t))
Using as a replacement for over _2second:
>>>over _2 show (10,20)(10,"20")
to :: (s -> a) -> SimpleGetter s a #
to creates a getter from any function:
a^.tof = f a
It's most useful in chains, because it lets you mix lenses and ordinary functions. Suppose you have a record which comes from some third-party library and doesn't have any lens accessors. You want to do something like this:
value ^. _1 . field . at 2
However, field isn't a getter, and you have to do this instead:
field (value ^. _1) ^. at 2
but now value is in the middle and it's hard to read the resulting code. A variant with to is prettier and more readable:
value ^. _1 . to field . at 2
(^.) :: s -> Getting a s a -> a infixl 8 #
(^.) applies a getter to a value; in other words, it gets a value out of a structure using a getter (which can be a lens, traversal, fold, etc.).
Getting 1st field of a tuple:
(^._1) :: (a, b) -> a (^._1) =fst
When (^.) is used with a traversal, it combines all results using the Monoid instance for the resulting type. For instance, for lists it would be simple concatenation:
>>>("str","ing") ^. each"string"
The reason for this is that traversals use Applicative, and the Applicative instance for Const uses monoid concatenation to combine “effects” of Const.
A non-operator version of (^.) is called view, and it's a bit more general than (^.) (it works in MonadReader). If you need the general version, you can get it from microlens-mtl; otherwise there's view available in Lens.Micro.Extras.