| Safe Haskell | Safe-Inferred | 
|---|
Lens.Family2.Unchecked
Contents
Description
Caution: Improper use of this module can lead to unexpected behaviour if the preconditions of the functions are not met.
- lens :: (a -> b) -> (a -> b' -> a') -> Lens a a' b b'
- iso :: (a -> b) -> (b' -> a') -> Lens a a' b b'
- setting :: ((b -> b') -> a -> a') -> Setter a a' b b'
- type Lens a a' b b' = forall f. Functor f => LensLike f a a' b b'
- type Lens' a b = forall f. Functor f => LensLike' f a b
- type Traversal a a' b b' = forall f. Applicative f => LensLike f a a' b b'
- type Traversal' a b = forall f. Applicative f => LensLike' f a b
- type Setter a a' b b' = forall f. Identical f => LensLike f a a' b b'
- type Setter' a b = forall f. Identical f => LensLike' f a b
- type LensLike f a a' b b' = (b -> f b') -> a -> f a'
- type LensLike' f a b = (b -> f b) -> a -> f a
- class Applicative f => Identical f
- class Functor f => Applicative f
Lenses
A lens family is created by separating a substructure from the rest of its structure by a functor. How to create a lens family is best illustrated by the common example of a field of a record:
 data MyRecord a = MyRecord { _myA :: a, _myB :: Int }
 -- The use of type variables a and a' allow for polymorphic updates.
 myA :: Lens (MyRecord a) (MyRecord a') a a'
 myA f (MyRecord a b) = (\a' -> MyRecord a' b) `fmap` (f a)
 -- The field _myB is monomorphic, so we can use a 'Lens'' type.
 -- However, the structure of the function is exactly the same as for Lens.
 myB :: Lens' (MyRecord a) Int
 myB f (MyRecord a b) = (\b' -> MyRecord a b') `fmap` (f b)
By following this template you can safely build your own lenses.
 To use this template, you do not need anything from this module other than the type synonyms Lens and Lens', and even they are optional.
 See the lens-family-th package to generate this code using Template Haskell.
Note: It is possible to build lenses without even depending on lens-family by expanding away the type synonym.
-- A lens definition that only requires the Haskell "Prelude". myA :: Functor f => (a -> f a') -> (MyRecord a) -> f (MyRecord a') myA f (MyRecord a b) = (\a' -> MyRecord a' b) `fmap` (f a)
You can build lenses for more than just fields of records.
 Any value l :: Lens a a' b b' is well-defined when it satisfies the two van Laarhoven lens laws:
- l Identity === Identity 
- l (Compose . fmap f . g) === Compose . fmap (l f) . (l g) 
The functions lens and iso can also be used to construct lenses.
 The resulting lenses will be well-defined so long as their preconditions are satisfied.
Traversals
If you have zero or more fields of the same type of a record, a traversal can be used to refer to all of them in order.
 Multiple references are made by replacing the Functor constraint of lenses with an Applicative constraint.
 Consider the following example of a record with two Int fields.
 data MyRecord = MyRecord { _myA :: Int, _myB :: Int }
 -- myInts is a traversal over both fields of MyRecord.
 myInts :: Traversal' MyRecord Int
 myInts f (MyRecord a b) = MyRecord <$> f a <*> f b
If the record and the referenced fields are parametric, you can can build traversals with polymorphic updating.
 Consider the following example of a record with two Maybe fields.
 data MyRecord a = MyRecord { _myA :: Maybe a, _myB :: Maybe a }
 -- myInts is a traversal over both fields of MyRecord.
 myMaybes :: Traversal (MyRecord a) (MyRecord a') (Maybe a) (Maybe a')
 myMaybes f (MyRecord a b) = MyRecord <$> f a <*> f b
Note: As with lenses, is possible to build traversals without even depending on lens-family-core by expanding away the type synonym.
-- A traversal definition that only requires the Haskell "Prelude". myMaybes :: Applicative f => (Maybe a -> f (Maybe a')) -> MyRecord a -> f (MyRecord a') myMaybes f (MyRecord a b) = MyRecord <$> f a <*> f b
Unfortuantely, there are no helper functions for making traversals. You must make them by hand.
Any value t :: Traversal a a' b b' is well-defined when it satisfies the two van Laarhoven traversal laws:
- t Identity === Identity 
- t (Compose . fmap f . g) === Compose . fmap (t f) . (t g) 
traverse is the canonical traversal for various containers.
Documentation
Arguments
| :: (a -> b) | getter | 
| -> (a -> b' -> a') | setter | 
| -> Lens a a' b b' | 
Build a lens from a getter and setter families.
Caution: In order for the generated lens family to be well-defined, you must ensure that the three lens laws hold:
- getter (setter a b) === b 
- setter a (getter a) === a 
- setter (setter a b1) b2) === setter a b2 
Arguments
| :: (a -> b) | yin | 
| -> (b' -> a') | yang | 
| -> Lens a a' b b' | 
Build a lens from isomorphism families.
Caution: In order for the generated lens family to be well-defined, you must ensure that the two isomorphism laws hold:
- yin . yang === id 
- yang . yin === id 
Arguments
| :: ((b -> b') -> a -> a') | sec (semantic editor combinator) | 
| -> Setter a a' b b' | 
setting promotes a "semantic editor combinator" to a modify-only lens.
 To demote a lens to a semantic edit combinator, use the section (l %~) or over l from Lens.Family2.
>>>setting map . fstL %~ length $ [("The",0),("quick",1),("brown",1),("fox",2)][(3,0),(5,1),(5,1),(3,2)]
Caution: In order for the generated setter family to be well-defined, you must ensure that the two functors laws hold:
- sec id === id 
- sec f . sec g === sec (f . g) 
Types
type Traversal a a' b b' = forall f. Applicative f => LensLike f a a' b b'Source
type Traversal' a b = forall f. Applicative f => LensLike' f a bSource
type LensLike f a a' b b' = (b -> f b') -> a -> f a'
type LensLike' f a b = (b -> f b) -> a -> f a
class Applicative f => Identical f
Re-exports
class Functor f => Applicative f
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying the following laws:
- identity
- 
      pureid<*>v = v
- composition
- 
      pure(.)<*>u<*>v<*>w = u<*>(v<*>w)
- homomorphism
- 
      puref<*>purex =pure(f x)
- interchange
- 
      u<*>purey =pure($y)<*>u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
      u *> v = pure (const id) <*> u <*> v
      u <* v = pure const <*> u <*> v
As a consequence of these laws, the Functor instance for f will satisfy
      fmap f x = pure f <*> x
If f is also a Monad, it should satisfy pure = return( (which implies that <*>) = appure and <*> satisfy the
 applicative functor laws).
Instances