Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- module Incipit
- type (@@) a b = Tagged b a
- module Prelate.Atomic
- module Prelate.Control.Monad
- module Prelate.Data.Maybe
- module Prelate.Json
- class ToJSON a
- class FromJSON a
- (&) :: a -> (a -> b) -> b
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- _Nothing :: Traversal' (Maybe a) ()
- _Just :: Traversal (Maybe a) (Maybe a') a a'
- _Right :: Traversal (Either a b) (Either a b') b b'
- _Left :: Traversal (Either a b) (Either a' b) a a'
- mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- _last :: Snoc s s a a => Traversal' s a
- _init :: Snoc s s a a => Traversal' s s
- _tail :: Cons s s a a => Traversal' s s
- _head :: Cons s s a a => Traversal' s a
- both :: Traversal (a, a) (b, b) a b
- filtered :: (a -> Bool) -> Traversal' a a
- failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b
- singular :: HasCallStack => Traversal s t a a -> Lens s t a a
- forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t
- traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t
- non :: Eq a => a -> Lens' (Maybe a) a
- folding :: Foldable f => (s -> f a) -> SimpleFold s a
- has :: Getting Any s a -> s -> Bool
- forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f ()
- traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f ()
- (^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a
- (^?) :: s -> Getting (First a) s a -> Maybe a
- toListOf :: Getting (Endo [a]) s a -> s -> [a]
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- to :: (s -> a) -> SimpleGetter s a
- (^.) :: s -> Getting a s a -> a
- transformOf :: ASetter a b a b -> (b -> b) -> a -> b
- rewriteOf :: ASetter a b a b -> (b -> Maybe a) -> a -> b
- (<<.~) :: LensLike ((,) a) s t a b -> b -> s -> (a, t)
- (<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t)
- (<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t)
- mapped :: Functor f => ASetter (f a) (f b) a b
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- (<>~) :: Monoid a => ASetter s t a a -> a -> s -> t
- (-~) :: Num a => ASetter s t a a -> a -> s -> t
- (+~) :: Num a => ASetter s t a a -> a -> s -> t
- over :: ASetter s t a b -> (a -> b) -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- sets :: ((a -> b) -> s -> t) -> ASetter s t a b
- folded :: forall (f :: Type -> Type) a. Foldable f => SimpleFold (f a) a
- traversed :: forall (f :: Type -> Type) a b. Traversable f => Traversal (f a) (f b) a b
- each :: Each s t a b => Traversal s t a b
- ix :: Ixed m => Index m -> Traversal' m (IxValue m)
- at :: At m => Index m -> Lens' m (Maybe (IxValue m))
- _1 :: Field1 s t a b => Lens s t a b
- _2 :: Field2 s t a b => Lens s t a b
- _3 :: Field3 s t a b => Lens s t a b
- _4 :: Field4 s t a b => Lens s t a b
- _5 :: Field5 s t a b => Lens s t a b
- strict :: Strict lazy strict => Lens' lazy strict
- lazy :: Strict lazy strict => Lens' strict lazy
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- type ASetter' s a = ASetter s s a a
- type SimpleGetter s a = forall r. Getting r s a
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- type SimpleFold s a = forall r. Monoid r => Getting r s a
- type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type Traversal s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t
- type Traversal' s a = Traversal s s a a
- type LensLike (f :: Type -> Type) s t a b = (a -> f b) -> s -> f t
- type LensLike' (f :: Type -> Type) s a = LensLike f s s a a
- at :: At m => Index m -> Lens' m (Maybe (IxValue m))
Documentation
module Incipit
module Prelate.Atomic
module Prelate.Control.Monad
module Prelate.Data.Maybe
module Prelate.Json
A type that can be converted to JSON.
Instances in general must specify toJSON
and should (but don't need
to) specify toEncoding
.
An example type and instance:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceToJSON
Coord wheretoJSON
(Coord x y) =object
["x".=
x, "y".=
y]toEncoding
(Coord x y) =pairs
("x".=
x<>
"y".=
y)
Instead of manually writing your ToJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
toJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
ToJSON
instance. If you require nothing other than
defaultOptions
, it is sufficient to write (and this is the only
alternative where the default toJSON
implementation is sufficient):
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceToJSON
Coord wheretoEncoding
=genericToEncoding
defaultOptions
If on the other hand you wish to customize the generic decoding, you have to implement both methods:
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceToJSON
Coord wheretoJSON
=genericToJSON
customOptionstoEncoding
=genericToEncoding
customOptions
Previous versions of this library only had the toJSON
method. Adding
toEncoding
had two reasons:
- toEncoding is more efficient for the common case that the output of
toJSON
is directly serialized to aByteString
. Further, expressing either method in terms of the other would be non-optimal. - The choice of defaults allows a smooth transition for existing users:
Existing instances that do not define
toEncoding
still compile and have the correct semantics. This is ensured by making the default implementation oftoEncoding
usetoJSON
. This produces correct results, but since it performs an intermediate conversion to aValue
, it will be less efficient than directly emitting anEncoding
. (this also means that specifying nothing more thaninstance ToJSON Coord
would be sufficient as a generically decoding instance, but there probably exists no good reason to not specifytoEncoding
in new instances.)
Instances
A type that can be converted from JSON, with the possibility of failure.
In many cases, you can get the compiler to generate parsing code for you (see below). To begin, let's cover writing an instance by hand.
There are various reasons a conversion could fail. For example, an
Object
could be missing a required key, an Array
could be of
the wrong size, or a value could be of an incompatible type.
The basic ways to signal a failed conversion are as follows:
fail
yields a custom error message: it is the recommended way of reporting a failure;empty
(ormzero
) is uninformative: use it when the error is meant to be caught by some(
;<|>
)typeMismatch
can be used to report a failure when the encountered value is not of the expected JSON type;unexpected
is an appropriate alternative when more than one type may be expected, or to keep the expected type implicit.
prependFailure
(or modifyFailure
) add more information to a parser's
error messages.
An example type and instance using typeMismatch
and prependFailure
:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceFromJSON
Coord whereparseJSON
(Object
v) = Coord<$>
v.:
"x"<*>
v.:
"y" -- We do not expect a non-Object
value here. -- We could useempty
to fail, buttypeMismatch
-- gives a much more informative error message.parseJSON
invalid =prependFailure
"parsing Coord failed, " (typeMismatch
"Object" invalid)
For this common case of only being concerned with a single
type of JSON value, the functions withObject
, withScientific
, etc.
are provided. Their use is to be preferred when possible, since
they are more terse. Using withObject
, we can rewrite the above instance
(assuming the same language extension and data type) as:
instanceFromJSON
Coord whereparseJSON
=withObject
"Coord" $ \v -> Coord<$>
v.:
"x"<*>
v.:
"y"
Instead of manually writing your FromJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
parseJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
FromJSON
instance for your datatype without giving
a definition for parseJSON
.
For example, the previous example can be simplified to just:
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceFromJSON
Coord
The default implementation will be equivalent to
parseJSON =
; if you need different
options, you can customize the generic decoding by defining:genericParseJSON
defaultOptions
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceFromJSON
Coord whereparseJSON
=genericParseJSON
customOptions
Instances
_Nothing :: Traversal' (Maybe a) () #
_Nothing
targets a ()
if the Maybe
is a Nothing
, and doesn't target anything otherwise:
>>>
Just 1 ^.. _Nothing
[]
>>>
Nothing ^.. _Nothing
[()]
It's not particularly useful (unless you want to use
as a replacement for has
_Nothing
isNothing
), and provided mainly for consistency.
Implementation:
_Nothing
f Nothing =const
Nothing
<$>
f ()_Nothing
_ j =pure
j
_Just :: Traversal (Maybe a) (Maybe a') a a' #
_Just
targets the value contained in a Maybe
, provided it's a Just
.
See documentation for _Left
(as these 2 are pretty similar). In particular, it can be used to write these:
- Unsafely extracting a value from a
Just
:
fromJust
= (^?!
_Just
)
- Checking whether a value is a
Just
:
isJust
=has
_Just
- Converting a
Maybe
to a list (empty or consisting of a single element):
maybeToList
= (^..
_Just
)
- Gathering all
Just
s in a list:
catMaybes
= (^..
each
.
_Just
)
_Left :: Traversal (Either a b) (Either a' b) a a' #
_Left
targets the value contained in an Either
, provided it's a Left
.
Gathering all Left
s in a structure (like the lefts
function, but not necessarily just for lists):
>>>
[Left 1, Right 'c', Left 3] ^.. each._Left
[1,3]
Checking whether an Either
is a Left
(like isLeft
):
>>>
has _Left (Left 1)
True
>>>
has _Left (Right 1)
False
Extracting a value (if you're sure it's a Left
):
>>>
Left 1 ^?! _Left
1
Mapping over all Left
s:
>>>
(each._Left %~ map toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]
Implementation:
_Left
f (Left a) =Left
<$>
f a_Left
_ (Right b) =pure
(Right
b)
mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) #
This generalizes mapAccumL
to an arbitrary Traversal
. (Note that it doesn't work on folds, only traversals.)
mapAccumL
≡mapAccumLOf
traverse
_last :: Snoc s s a a => Traversal' s a #
_init :: Snoc s s a a => Traversal' s s #
_tail :: Cons s s a a => Traversal' s s #
_tail
gives you access to the tail of a list (or Seq
, etc):
>>>
[1..5] ^? _tail
Just [2,3,4,5]
You can modify the tail as well:
>>>
[4,1,2,3] & _tail %~ reverse
[4,3,2,1]
Since lists are monoids, you can use _tail
with plain (^.
) (and then it'll return an empty list if you give it an empty list):
>>>
[1..5] ^. _tail
[2,3,4,5]
>>>
[] ^. _tail
[]
If you want to traverse each element of the tail, use _tail
with each
:
>>>
"I HATE CAPS." & _tail.each %~ toLower
"I hate caps."
This package only lets you use _tail
on lists, but if you use microlens-ghc you get instances for ByteString
and Seq
, and if you use microlens-platform you additionally get instances for Text
and Vector
.
_head :: Cons s s a a => Traversal' s a #
_head
traverses the 1st element of something (usually a list, but can also be a Seq
, etc):
>>>
[1..5] ^? _head
Just 1
It can be used to modify too, as in this example where the 1st letter of a sentence is capitalised:
>>>
"mary had a little lamb." & _head %~ toTitle
"Mary had a little lamb."
The reason it's a traversal and not a lens is that there's nothing to traverse when the list is empty:
>>>
[] ^? _head
Nothing
This package only lets you use _head
on lists, but if you use microlens-ghc you get instances for ByteString
and Seq
, and if you use microlens-platform you additionally get instances for Text
and Vector
.
filtered :: (a -> Bool) -> Traversal' a a #
filtered
is a traversal that filters elements “passing” through it:
>>>
(1,2,3,4) ^.. each
[1,2,3,4]
>>>
(1,2,3,4) ^.. each . filtered even
[2,4]
It also can be used to modify elements selectively:
>>>
(1,2,3,4) & each . filtered even %~ (*100)
(1,200,3,400)
The implementation of filtered
is very simple. Consider this traversal, which always “traverses” just the value it's given:
id :: Traversal'
a a
id f s = f s
And this traversal, which traverses nothing (in other words, doesn't traverse the value it's given):
ignored ::Traversal'
a a ignored f s =pure
s
And now combine them into a traversal that conditionally traverses the value it's given, and you get filtered
:
filtered :: (a -> Bool) ->Traversal'
a a filtered p f s = if p s then f s elsepure
s
By the way, note that filtered
can generate illegal traversals – sometimes this can bite you. In particular, an optimisation that should be safe becomes unsafe. (To the best of my knowledge, this optimisation never happens automatically. If you just use filtered
to modify/view something, you're safe. If you don't define any traversals that use filtered
, you're safe too.)
Let's use evens
as an example:
evens =filtered
even
If evens
was a legal traversal, you'd be able to fuse several applications of evens
like this:
over
evens f.
over
evens g =over
evens (f.
g)
Unfortunately, in case of evens
this isn't a correct optimisation:
- the left-side variant applies
g
to all even numbers, and then appliesf
to all even numbers that are left afterf
(becausef
might've turned some even numbers into odd ones) - the right-side variant applies
f
andg
to all even numbers
Of course, when you are careful and know what you're doing, you won't try to make such an optimisation. However, if you export an illegal traversal created with filtered
and someone tries to use it, they might mistakenly assume that it's legal, do the optimisation, and silently get an incorrect result.
If you are using filtered
with some another traversal that doesn't overlap with -whatever the predicate checks-, the resulting traversal will be legal. For instance, here the predicate looks at the 1st element of a tuple, but the resulting traversal only gives you access to the 2nd:
pairedWithEvens ::Traversal
[(Int, a)] [(Int, b)] a b pairedWithEvens =each
.
filtered
(even
.
fst
).
_2
Since you can't do anything with the 1st components through this traversal, the following holds for any f
and g
:
over
pairedWithEvens f.
over
pairedWithEvens g =over
pairedWithEvens (f.
g)
failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b infixl 5 #
failing
lets you chain traversals together; if the 1st traversal fails, the 2nd traversal will be used.
>>>
([1,2],[3]) & failing (_1.each) (_2.each) .~ 0
([0,0],[3])
>>>
([],[3]) & failing (_1.each) (_2.each) .~ 0
([],[0])
Note that the resulting traversal won't be valid unless either both traversals don't touch each others' elements, or both traversals return exactly the same results. To see an example of how failing
can generate invalid traversals, see this Stackoverflow question.
singular :: HasCallStack => Traversal s t a a -> Lens s t a a #
singular
turns a traversal into a lens that behaves like a single-element traversal:
>>>
[1,2,3] ^. singular each
1
>>>
[1,2,3] & singular each %~ negate
[-1,2,3]
If there is nothing to return, it'll throw an error:
>>>
[] ^. singular each
*** Exception: Lens.Micro.singular: empty traversal
However, it won't fail if you are merely setting the value:
>>>
[] & singular each %~ negate
forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t #
traverseOf
with flipped arguments. Useful if the “loop body” is a lambda or
a do
block.
traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t #
Apply an action to all targets (like mapM
or traverse
):
>>>
traverseOf both readFile ("file1", "file2")
(<contents of file1>, <contents of file2>)
>>>
traverseOf _1 id (Just 1, 2)
Just (1, 2)>>>
traverseOf _1 id (Nothing, 2)
Nothing
You can also just apply the lens/traversal directly (but traverseOf
might be more readable):
>>>
both readFile ("file1", "file2")
(<contents of file1>, <contents of file2>)
If you don't need the result, use traverseOf_
.
non :: Eq a => a -> Lens' (Maybe a) a #
non
lets you “relabel” a Maybe
by equating Nothing
to an arbitrary value (which you can choose):
>>>
Just 1 ^. non 0
1
>>>
Nothing ^. non 0
0
The most useful thing about non
is that relabeling also works in other direction. If you try to set
the “forbidden” value, it'll be turned to Nothing
:
>>>
Just 1 & non 0 .~ 0
Nothing
Setting anything else works just fine:
>>>
Just 1 & non 0 .~ 5
Just 5
Same happens if you try to modify a value:
>>>
Just 1 & non 0 %~ subtract 1
Nothing
>>>
Just 1 & non 0 %~ (+ 1)
Just 2
non
is often useful when combined with at
. For instance, if you have a map of songs and their playcounts, it makes sense not to store songs with 0 plays in the map; non
can act as a filter that wouldn't pass such entries.
Decrease playcount of a song to 0, and it'll be gone:
>>>
fromList [("Soon",1),("Yesterday",3)] & at "Soon" . non 0 %~ subtract 1
fromList [("Yesterday",3)]
Try to add a song with 0 plays, and it won't be added:
>>>
fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 0
fromList [("Yesterday",3)]
But it will be added if you set any other number:
>>>
fromList [("Yesterday",3)] & at "Soon" . non 0 .~ 1
fromList [("Soon",1),("Yesterday",3)]
non
is also useful when working with nested maps. Here a nested map is created when it's missing:
>>>
Map.empty & at "Dez Mona" . non Map.empty . at "Soon" .~ Just 1
fromList [("Dez Mona",fromList [("Soon",1)])]
and here it is deleted when its last entry is deleted (notice that non
is used twice here):
>>>
fromList [("Dez Mona",fromList [("Soon",1)])] & at "Dez Mona" . non Map.empty . at "Soon" . non 0 %~ subtract 1
fromList []
To understand the last example better, observe the flow of values in it:
- the map goes into
at "Dez Mona"
- the nested map (wrapped into
Just
) goes intonon Map.empty
Just
is unwrapped and the nested map goes intoat "Soon"
Just 1
is unwrapped bynon 0
Then the final value – i.e. 1 – is modified by subtract 1
and the result (which is 0) starts flowing backwards:
non 0
sees the 0 and produces aNothing
at "Soon"
seesNothing
and deletes the corresponding value from the map- the resulting empty map is passed to
non Map.empty
, which sees that it's empty and thus producesNothing
at "Dez Mona"
seesNothing
and removes the key from the map
folding :: Foldable f => (s -> f a) -> SimpleFold s a #
has :: Getting Any s a -> s -> Bool #
has
checks whether a getter (any getter, including lenses, traversals, and folds) returns at least 1 value.
Checking whether a list is non-empty:
>>>
has each []
False
You can also use it with e.g. _Left
(and other 0-or-1 traversals) as a replacement for isNothing
, isJust
and other isConstructorName
functions:
>>>
has _Left (Left 1)
True
forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f () #
traverseOf_
with flipped arguments. Useful if the “loop body” is a lambda
or a do
block, or in some other cases – for instance, you can avoid
accidentally using for_
on a tuple or Either
by switching
to
. Or you can write custom loops like these:forOf_
each
forOf_
both
(a, b) $ \x -> ...forOf_
each
[1..10] $ \x -> ...forOf_
(each
._Right
) $ \x -> ...
traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f () #
Apply an action to all targets and discard the result (like mapM_
or traverse_
):
>>>
traverseOf_ both putStrLn ("hello", "world")
hello world
Works with anything that allows getting, including lenses and getters (so, anything except for ASetter
). Should be faster than traverseOf
when you don't need the result.
(^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a infixl 8 #
(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 #
s ^? t
returns the 1st element t
returns, or Nothing
if t
doesn't return anything. It's trivially implemented by passing the First
monoid to the getter.
Safe head
:
>>>
[] ^? each
Nothing
>>>
[1..3] ^? each
Just 1
>>>
Left 1 ^? _Right
Nothing
>>>
Right 1 ^? _Right
Just 1
A non-operator version of (^?
) is called preview
, and – like view
– 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 preview
available in Lens.Micro.Extras.
(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 #
s ^.. t
returns the list of all values that t
gets from s
.
A Maybe
contains either 0 or 1 values:
>>>
Just 3 ^.. _Just
[3]
Gathering all values in a list of tuples:
>>>
[(1,2),(3,4)] ^.. each.each
[1,2,3,4]
to :: (s -> a) -> SimpleGetter s a #
to
creates a getter from any function:
a^.
to
f = 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.
transformOf :: ASetter a b a b -> (b -> b) -> a -> b #
Transform every element by recursively applying a given ASetter
in a bottom-up manner.
Since: microlens-0.4.11
rewriteOf :: ASetter a b a b -> (b -> Maybe a) -> a -> b #
→ See an example on GitHub.
Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result.
Usually transformOf
is more appropriate, but rewriteOf
can give better compositionality. Given two single transformations f
and g
, you can construct \a -> f a
which performs both rewrites until a fixed point.<|>
g a
Since: microlens-0.4.11
(<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t) infixr 4 #
This is a version of (%~
) which modifies the structure and returns it along with the new value:
>>>
(1, 2) & _1 <%~ negate
(-1, (-1, 2))
Simpler type signatures:
(<%~
) ::Lens
s t a b -> (a -> b) -> s -> (b, t) (<%~
) ::Monoid
b =>Traversal
s t a b -> (a -> b) -> s -> (b, t)
Since it does getting in addition to setting, you can't use it with ASetter
(but you can use it with lens and traversals).
mapped :: Functor f => ASetter (f a) (f b) a b #
mapped
is a setter for everything contained in a functor. You can use it to map over lists, Maybe
, or even IO
(which is something you can't do with traversed
or each
).
Here mapped
is used to turn a value to all non-Nothing
values in a list:
>>>
[Just 3,Nothing,Just 5] & mapped.mapped .~ 0
[Just 0,Nothing,Just 0]
Keep in mind that while mapped
is a more powerful setter than each
, it can't be used as a getter! This won't work (and will fail with a type error):
[(1,2),(3,4),(5,6)]^..
mapped
.both
(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t infixr 4 #
(<>~
) appends a value monoidally to the target.
>>>
("hello", "goodbye") & both <>~ " world!"
("hello world!", "goodbye world!")
Since: microlens-0.4.9
(-~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 #
Decrement the target(s) of a numerically valued Lens
, or Traversal
.
>>>
(a,b) & _1 -~ c
(a - c,b)
>>>
(a,b) & both -~ c
(a - c,b - c)
>>>
_1 -~ 2 $ (1,2)
(-1,2)
>>>
mapped.mapped -~ 1 $ [[4,5],[6,7]]
[[3,4],[5,6]]
(-~
) ::Num
a =>Lens'
s a -> a -> s -> s (-~
) ::Num
a =>Traversal'
s a -> a -> s -> s
Since: microlens-0.4.10
(+~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 #
Increment the target(s) of a numerically valued Lens
or Traversal
.
>>>
(a,b) & _1 +~ c
(a + c,b)
>>>
(a,b) & both +~ c
(a + c,b + c)
>>>
(1,2) & _2 +~ 1
(1,3)
>>>
[(a,b),(c,d)] & traverse.both +~ e
[(a + e,b + e),(c + e,d + e)]
(+~
) ::Num
a =>Lens'
s a -> a -> s -> s (+~
) ::Num
a =>Traversal'
s a -> a -> s -> s
Since: microlens-0.4.10
over :: ASetter s t a b -> (a -> b) -> s -> t #
Getting fmap
in a roundabout way:
over
mapped
::Functor
f => (a -> b) -> f a -> f bover
mapped
=fmap
Applying a function to both components of a pair:
over
both
:: (a -> b) -> (a, a) -> (b, b)over
both
= \f t -> (f (fst t), f (snd t))
Using
as a replacement for over
_2
second
:
>>>
over _2 show (10,20)
(10,"20")
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #
(%~
) applies a function to the target; an alternative explanation is that it is an inverse of sets
, which turns a setter into an ordinary function.
is the same thing as mapped
%~
reverse
.fmap
reverse
See over
if you want a non-operator synonym.
Negating the 1st element of a pair:
>>>
(1,2) & _1 %~ negate
(-1,2)
Turning all Left
s in a list to upper case:
>>>
(mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]
traversed :: forall (f :: Type -> Type) a b. Traversable f => Traversal (f a) (f b) a b #
traversed
traverses any Traversable
container (list, vector, Map
, Maybe
, you name it):
>>>
Just 1 ^.. traversed
[1]
traversed
is the same as traverse
, but can be faster thanks to magic rewrite rules.
each :: Each s t a b => Traversal s t a b #
each
tries to be a universal Traversal
– it behaves like traversed
in most situations, but also adds support for e.g. tuples with same-typed values:
>>>
(1,2) & each %~ succ
(2,3)
>>>
["x", "y", "z"] ^. each
"xyz"
However, note that each
doesn't work on every instance of Traversable
. If you have a Traversable
which isn't supported by each
, you can use traversed
instead. Personally, I like using each
instead of traversed
whenever possible – it's shorter and more descriptive.
You can use each
with these things:
each
::Traversal
[a] [b] a beach
::Traversal
(Maybe
a) (Maybe
b) a beach
::Traversal
(Either
a a) (Either
b b) a b -- since 0.4.11each
::Traversal
(a,a) (b,b) a beach
::Traversal
(a,a,a) (b,b,b) a beach
::Traversal
(a,a,a,a) (b,b,b,b) a beach
::Traversal
(a,a,a,a,a) (b,b,b,b,b) a beach
:: (RealFloat
a,RealFloat
b) =>Traversal
(Complex
a) (Complex
b) a b
You can also use each
with types from array, bytestring, and containers by using microlens-ghc, or additionally with types from vector, text, and unordered-containers by using microlens-platform.
ix :: Ixed m => Index m -> Traversal' m (IxValue m) #
This traversal lets you access (and update) an arbitrary element in a list, array, Map
, etc. (If you want to insert or delete elements as well, look at at
.)
An example for lists:
>>>
[0..5] & ix 3 .~ 10
[0,1,2,10,4,5]
You can use it for getting, too:
>>>
[0..5] ^? ix 3
Just 3
Of course, the element may not be present (which means that you can use ix
as a safe variant of (!!
)):
>>>
[0..5] ^? ix 10
Nothing
Another useful instance is the one for functions – it lets you modify their outputs for specific inputs. For instance, here's maximum
that returns 0 when the list is empty (instead of throwing an exception):
maximum0 =maximum
&
ix
[].~
0
The following instances are provided in this package:
ix
::Int
->Traversal'
[a] aix
::Int
->Traversal'
(NonEmpty a) aix
:: (Eq
e) => e ->Traversal'
(e -> a) a
You can also use ix
with types from array, bytestring, and containers by using microlens-ghc, or additionally with types from vector, text, and unordered-containers by using microlens-platform.
at :: At m => Index m -> Lens' m (Maybe (IxValue m)) #
This lens lets you read, write, or delete elements in Map
-like structures. It returns Nothing
when the value isn't found, just like lookup
:
Data.Map.lookup k m = m ^.
at k
However, it also lets you insert and delete values by setting the value to
or Just
valueNothing
:
Data.Map.insert k a m = m&
at k.~
Just a Data.Map.delete k m = m&
at k.~
Nothing
Or you could use (?~
) instead of (.~
):
Data.Map.insert k a m = m&
at k?~
a
Note that at
doesn't work for arrays or lists. You can't delete an arbitrary element from an array (what would be left in its place?), and you can't set an arbitrary element in a list because if the index is out of list's bounds, you'd have to somehow fill the stretch between the last element and the element you just inserted (i.e. [1,2,3] & at 10 .~ 5
is undefined). If you want to modify an already existing value in an array or list, you should use ix
instead.
at
is often used with non
. See the documentation of non
for examples.
Note that at
isn't strict for Map
, even if you're using Data.Map.Strict
:
>>>
Data.Map.Strict.size (Data.Map.Strict.empty & at 1 .~ Just undefined)
1
The reason for such behavior is that there's actually no “strict Map
” type; Data.Map.Strict
just provides some strict functions for ordinary Map
s.
This package doesn't actually provide any instances for at
, but there are instances for Map
and IntMap
in microlens-ghc and an instance for HashMap
in microlens-platform.
_1 :: Field1 s t a b => Lens s t a b #
Gives access to the 1st field of a tuple (up to 5-tuples).
Getting the 1st component:
>>>
(1,2,3,4,5) ^. _1
1
Setting the 1st component:
>>>
(1,2,3) & _1 .~ 10
(10,2,3)
Note that this lens is lazy, and can set fields even of undefined
:
>>>
set _1 10 undefined :: (Int, Int)
(10,*** Exception: Prelude.undefined
This is done to avoid violating a lens law stating that you can get back what you put:
>>>
view _1 . set _1 10 $ (undefined :: (Int, Int))
10
The implementation (for 2-tuples) is:
_1
f t = (,)<$>
f (fst
t)<*>
pure
(snd
t)
or, alternatively,
_1
f ~(a,b) = (\a' -> (a',b))<$>
f a
(where ~
means a lazy pattern).
strict :: Strict lazy strict => Lens' lazy strict #
strict
lets you convert between strict and lazy versions of a datatype:
>>>
let someText = "hello" :: Lazy.Text
>>>
someText ^. strict
"hello" :: Strict.Text
It can also be useful if you have a function that works on a strict type but your type is lazy:
stripDiacritics :: Strict.Text -> Strict.Text stripDiacritics = ...
>>>
let someText = "Paul Erdős" :: Lazy.Text
>>>
someText & strict %~ stripDiacritics
"Paul Erdos" :: Lazy.Text
strict
works on ByteString
and StateT
/WriterT
/RWST
if you use microlens-ghc, and additionally on Text
if you use microlens-platform.
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 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
::Getting
a s a -> s -> aview
::SimpleGetter
s a -> s -> aview
getter =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 SimpleGetter
s 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.
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 SimpleFold s a = forall r. Monoid r => Getting r s a #
A SimpleFold s a
extracts several a
s from s
; so, it's pretty much the same thing as (s -> [a])
, but you can use it with lens operators.
The actual Fold
from lens is more general:
type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
There are several functions in lens that accept lens's Fold
but won't accept SimpleFold
; I'm aware of
takingWhile
,
droppingWhile
,
backwards
,
foldByOf
,
foldMapByOf
.
For this reason, try not to export SimpleFold
s if at all possible. microlens-contra provides a fully lens-compatible Fold
.
Lens users: you can convert a SimpleFold
to Fold
by applying folded . toListOf
to it.
type Lens s t a b = forall (f :: Type -> Type). 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.
a
is the type of the value inside of structureb
is the type of the replaced values
is the type of the whole structuret
is the type of the structure after replacinga
in 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 Traversal s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t #
Traversal s t a b
is a generalisation of Lens
which allows many targets (possibly 0). It's achieved by changing the constraint to Applicative
instead of Functor
– indeed, the point of Applicative
is that you can combine effects, which is just what we need to have many targets.
Ultimately, traversals should follow 2 laws:
t pure ≡ pure fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g)
The 1st law states that you can't change the shape of the structure or do anything funny with elements (traverse elements which aren't in the structure, create new elements out of thin air, etc.). The 2nd law states that you should be able to fuse 2 identical traversals into one. For a more detailed explanation of the laws, see this blog post (if you prefer rambling blog posts), or The Essence Of The Iterator Pattern (if you prefer papers).
Traversing any value twice is a violation of traversal laws. You can, however, traverse values in any order.
type Traversal' s a = Traversal s s a a #
This is a type alias for monomorphic traversals which don't change the type of the container (or of the values inside).
type LensLike (f :: Type -> Type) s t a b = (a -> f b) -> s -> f t #
LensLike
is a type that is often used to make combinators as general as possible. For instance, take (<<%~
), which only requires the passed lens to be able to work with the (,) a
functor (lenses and traversals can do that). The fully expanded type is as follows:
(<<%~
) :: ((a -> (a, b)) -> s -> (a, t)) -> (a -> b) -> s -> (a, t)
With LensLike
, the intent to use the (,) a
functor can be made a bit clearer:
(<<%~
) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t)
type LensLike' (f :: Type -> Type) s a = LensLike f s s a a #
A type alias for monomorphic LensLike
s.
at :: At m => Index m -> Lens' m (Maybe (IxValue m)) #
This lens lets you read, write, or delete elements in Map
-like structures. It returns Nothing
when the value isn't found, just like lookup
:
Data.Map.lookup k m = m ^.
at k
However, it also lets you insert and delete values by setting the value to
or Just
valueNothing
:
Data.Map.insert k a m = m&
at k.~
Just a Data.Map.delete k m = m&
at k.~
Nothing
Or you could use (?~
) instead of (.~
):
Data.Map.insert k a m = m&
at k?~
a
Note that at
doesn't work for arrays or lists. You can't delete an arbitrary element from an array (what would be left in its place?), and you can't set an arbitrary element in a list because if the index is out of list's bounds, you'd have to somehow fill the stretch between the last element and the element you just inserted (i.e. [1,2,3] & at 10 .~ 5
is undefined). If you want to modify an already existing value in an array or list, you should use ix
instead.
at
is often used with non
. See the documentation of non
for examples.
Note that at
isn't strict for Map
, even if you're using Data.Map.Strict
:
>>>
Data.Map.Strict.size (Data.Map.Strict.empty & at 1 .~ Just undefined)
1
The reason for such behavior is that there's actually no “strict Map
” type; Data.Map.Strict
just provides some strict functions for ordinary Map
s.
This package doesn't actually provide any instances for at
, but there are instances for Map
and IntMap
in microlens-ghc and an instance for HashMap
in microlens-platform.