lens-family-2.1.0: Lens Families

Safe HaskellSafe
LanguageHaskell98

Lens.Family2

Contents

Description

This is the main module for end-users of lens-families. If you are not building your own optics such as lenses, traversals, grates, etc., but just using optics made by others, this is the only module you need.

Synopsis

Lenses

This module provides ^. for accessing fields and .~ and %~ for setting and modifying fields. Lenses are composed with . from the Prelude and id is the identity lens.

Lens composition in this library enjoys the following identities.

  • x^.l1.l2 === x^.l1^.l2
  • l1.l2 %~ f === l1 %~ l2 %~ f

The identity lens behaves as follows.

  • x^.id === x
  • id %~ f === f

The & operator, allows for a convenient way to sequence record updating:

record & l1 .~ value1 & l2 .~ value2

Lenses are implemented in van Laarhoven style. Lenses have type Functor f => (a -> f a) -> s -> f s and lens families have type Functor f => (a i -> f (a j)) -> s i -> f (s j).

Keep in mind that lenses and lens families can be used directly for functorial updates. For example, _2 id gives you strength.

_2 id :: Functor f => (a, f b) -> f (a, b)

Here is an example of code that uses the Maybe functor to preserves sharing during update when possible.

-- | 'sharedUpdate' returns the *identical* object if the update doesn't change anything.
-- This is useful for preserving sharing.
sharedUpdate :: Eq a => LensLike' Maybe s a -> (a -> a) -> s -> s
sharedUpdate l f s = fromMaybe s (l f' s)
 where
  f' a | b == a    = Nothing
       | otherwise = Just b
   where
    b = f a

Traversals

^. can be used with traversals to access monoidal fields. The result will be a mconcat of all the fields referenced. The various fooOf functions can be used to access different monoidal summaries of some kinds of values.

^? can be used to access the first value of a traversal. Nothing is returned when the traversal has no references.

^.. can be used with a traversals and will return a list of all fields referenced.

When .~ is used with a traversal, all referenced fields will be set to the same value, and when %~ is used with a traversal, all referenced fields will be modified with the same function.

A variant of ^? call matching returns Either a Right value which is the first value of the traversal, or a Left value which is a "proof" that the traversal has no elements. The "proof" consists of the original input structure, but in the case of polymorphic families, the type parameter is replaced with a fresh type variable, thus proving that the type parameter was unused.

Like all optics, traversals can be composed with ., and because every lens is automatically a traversal, lenses and traversals can be composed with . yielding a traversal.

Traversals are implemented in van Laarhoven style. Traversals have type Applicative f => (a -> f a) -> s -> f s and traversal families have type Applicative f => (a i -> f (a j)) -> s i -> f (s j).

Grates

zipWithOf can be used with grates to zip two structure together provided a binary operation.

under can be to modify each value in a structure according to a function. This works analogous to how over works for lenses and traversals.

review can be used with grates to construct a constant grate from a single value. This is like a 0-ary zipWith function.

degrating can be used to build higher arity zipWithOf functions:

zipWith3Of :: AGrate s t a b -> (a -> a -> a -> b) -> s -> s -> s -> t
zipWith3Of l f s1 s2 s3 = degrating l (\k -> f (k s1) (k s2) (k s3))

Like all optics, grates can be composed with ., and id is the identity grate.

Grates are implemented in van Laarhoven style.

Grates have type Functor g => (g a -> a) -> g s -> s and grate families have type Functor g => (g (a i) -> a j) -> g (s i) -> s j.

Keep in mind that grates and grate families can be used directly for functorial zipping. For example,

both sum :: Num a => [(a, a)] -> (a, a)

will take a list of pairs return the sum of the first components and the sum of the second components. For another example,

cod id :: Functor f => f (r -> a) -> r -> f a

will turn a functor full of functions into a function returning a functor full of results.

Adapters, Grids, and Prisms

The Adapter, Prism, and Grid optics are all AdapterLike optics and typically not used directly, but either converted to a LensLike optic using under, or into a GrateLike optic using over. See under and over for details about which conversions are possible.

These optics are implemented in van Laarhoven style.

Keep in mind that these optics and their families can sometimes be used directly, without using over and under. Sometimes you can take advantage of the fact that

   LensLike f (g s) t (g a) b
  ==
   AdapterLike f g s t a b
  ==
   GrateLike g s (f t) a (f b)

For example, if you have a grid for your structure to another type that has an Arbitray instance, such as grid from a custom word type to Bool, e.g. myWordBitVector :: (Applicative f, Functor g) => AdapterLike' f g MyWord Bool, you can use the grid to create an Arbitrary instance for your structure by directly applying review:

instance Arbitrary MyWord where
  arbitrary = review myWordBitVector arbitrary

Building and Finding Optics

Documentation

to :: (s -> a) -> Getter s t a b Source #

to promotes a projection function to a read-only lens called a getter. To demote a lens to a projection function, use the section (^.l) or view l.

>>> (3 :+ 4, "example")^._1.to(abs)
5.0 :+ 0.0

view :: FoldLike a s t a b -> s -> a #

view :: Getter s t a b -> s -> a

Demote a lens or getter to a projection function.

view :: Monoid a => Fold s t a b -> s -> a

Returns the monoidal summary of a traversal or a fold.

(^.) :: s -> FoldLike a s t a b -> a infixl 8 #

(^.) :: s -> Getter s t a b -> a

Access the value referenced by a getter or lens.

(^.) :: Monoid a => s -> Fold s t a b -> a

Access the monoidal summary referenced by a traversal or a fold.

folding :: Foldable f => (s -> f a) -> Fold s t a b Source #

folding promotes a "toList" function to a read-only traversal called a fold.

To demote a traversal or fold to a "toList" function use the section (^..l) or toListOf l.

views :: FoldLike r s t a b -> (a -> r) -> s -> r #

views :: Monoid r => Fold s t a b -> (a -> r) -> s -> r

Given a fold or traversal, return the foldMap of all the values using the given function.

views :: Getter s t a b -> (a -> r) -> s -> r

views is not particularly useful for getters or lenses, but given a getter or lens, it returns the referenced value passed through the given function.

views l f s = f (view l s)

(^..) :: s -> Fold s t a b -> [a] infixl 8 Source #

Returns a list of all of the referenced values in order.

(^?) :: s -> Fold s t a b -> Maybe a infixl 8 Source #

Returns Just the first referenced value. Returns Nothing if there are no referenced values.

toListOf :: Fold s t a b -> s -> [a] Source #

Returns a list of all of the referenced values in order.

allOf :: Fold s t a b -> (a -> Bool) -> s -> Bool Source #

Returns true if all of the referenced values satisfy the given predicate.

anyOf :: Fold s t a b -> (a -> Bool) -> s -> Bool Source #

Returns true if any of the referenced values satisfy the given predicate.

firstOf :: Fold s t a b -> s -> Maybe a Source #

Returns Just the first referenced value. Returns Nothing if there are no referenced values. See ^? for an infix version of firstOf

lastOf :: Fold s t a b -> s -> Maybe a Source #

Returns Just the last referenced value. Returns Nothing if there are no referenced values.

sumOf :: Num a => Fold s t a b -> s -> a Source #

Returns the sum of all the referenced values.

productOf :: Num a => Fold s t a b -> s -> a Source #

Returns the product of all the referenced values.

lengthOf :: Num r => Fold s t a b -> s -> r Source #

Counts the number of references in a traversal or fold for the input.

nullOf :: Fold s t a b -> s -> Bool Source #

Returns true if the number of references in the input is zero.

matching :: Traversal s t a b -> s -> Either t a Source #

Returns Right of the first referenced value. Returns Left the original value when there are no referenced values. In case there are no referenced values, the result might have a fresh type parameter, thereby proving the original value had no referenced values.

over :: Setter s t a b -> (a -> b) -> s -> t Source #

Demote a setter to a semantic editor combinator.

over :: Prism s t a b -> Reviwer s t a b
over :: Grid s t a b -> Grate s t a b
over :: Adapter s t a b -> Grate s t a b

Covert an AdapterLike optic into a GrateLike optic.

(%~) :: Setter s t a b -> (a -> b) -> s -> t infixr 4 Source #

Modify all referenced fields.

set :: Setter s t a b -> b -> s -> t Source #

Set all referenced fields to the given value.

(.~) :: Setter s t a b -> b -> s -> t infixr 4 Source #

Set all referenced fields to the given value.

review :: GrateLike (Constant () :: Type -> Type) s t a b -> b -> t #

review :: Grate s t a b -> b -> t
review :: Reviewer s t a b -> b -> t

zipWithOf :: Grate s t a b -> (a -> a -> b) -> s -> s -> t Source #

Returns a binary instance of a grate.

zipWithOf l f x y = degrating l (k -> f (k x) (k y))

degrating :: Grate s t a b -> ((s -> a) -> b) -> t Source #

Demote a grate to its normal, higher-order function, form.

degrating . grate = id
grate . degrating = id

under :: Resetter s t a b -> (a -> b) -> s -> t Source #

Demote a resetter to a semantic editor combinator.

under :: Prism s t a b -> Traversal s t a b
under :: Grid s t a b -> Traversal s t a b
under :: Adapter s t a b -> Lens s t a b

Covert an AdapterLike optic into a LensLike optic.

Note: this function is unrelated to the lens package's under function.

reset :: Resetter s t a b -> b -> s -> t Source #

Set all referenced fields to the given value.

(&) :: s -> (s -> t) -> t infixl 1 #

A flipped version of ($).

Pseudo-imperatives

(+~) :: Num a => Setter s t a a -> a -> s -> t infixr 4 Source #

(*~) :: Num a => Setter s t a a -> a -> s -> t infixr 4 Source #

(-~) :: Num a => Setter s t a a -> a -> s -> t infixr 4 Source #

(//~) :: Fractional a => Setter s t a a -> a -> s -> t infixr 4 Source #

(&&~) :: Setter s t Bool Bool -> Bool -> s -> t infixr 4 Source #

(||~) :: Setter s t Bool Bool -> Bool -> s -> t infixr 4 Source #

(<>~) :: Monoid a => Setter s t a a -> a -> s -> t infixr 4 Source #

Monoidally append a value to all referenced fields.

Types

type Adapter s t a b = forall f g. (Functor f, Functor g) => AdapterLike f g s t a b Source #

type Adapter' s a = forall f g. (Functor f, Functor g) => AdapterLike' f g s a Source #

type Prism s t a b = forall f g. (Applicative f, Traversable g) => AdapterLike f g s t a b Source #

type Prism' s a = forall f g. (Applicative f, Traversable g) => AdapterLike' f g s a Source #

type Lens s t a b = forall f. Functor f => LensLike f s t a b Source #

type Lens' s a = forall f. Functor f => LensLike' f s a Source #

type Traversal s t a b = forall f. Applicative f => LensLike f s t a b Source #

type Traversal' s a = forall f. Applicative f => LensLike' f s a Source #

type Setter s t a b = forall f. Identical f => LensLike f s t a b Source #

type Setter' s a = forall f. Identical f => LensLike' f s a Source #

type Getter s t a b = forall f. Phantom f => LensLike f s t a b Source #

type Getter' s a = forall f. Phantom f => LensLike' f s a Source #

type Fold s t a b = forall f. (Phantom f, Applicative f) => LensLike f s t a b Source #

type Fold' s a = forall f. (Phantom f, Applicative f) => LensLike' f s a Source #

type Grate s t a b = forall g. Functor g => GrateLike g s t a b Source #

type Grate' s a = forall g. Functor g => GrateLike' g s a Source #

type Grid s t a b = forall f g. (Applicative f, Functor g) => AdapterLike f g s t a b Source #

type Grid' s a = forall f g. (Applicative f, Functor g) => AdapterLike' f g s a Source #

type Reviewer s t a b = forall f. Phantom f => GrateLike f s t a b Source #

type Reviewer' s a = forall f. Phantom f => GrateLike' f s a Source #

type AdapterLike (f :: Type -> Type) (g :: Type -> Type) s t a b = (g a -> f b) -> g s -> f t #

type AdapterLike' (f :: Type -> Type) (g :: Type -> Type) s a = (g a -> f a) -> g s -> f s #

type LensLike (f :: Type -> Type) s t a b = (a -> f b) -> s -> f t #

type LensLike' (f :: Type -> Type) s a = (a -> f a) -> s -> f s #

type GrateLike (g :: Type -> Type) s t a b = (g a -> b) -> g s -> t #

type GrateLike' (g :: Type -> Type) s a = (g a -> a) -> g s -> s #

type FoldLike r s t a b = LensLike (Constant r :: Type -> Type) s t a b #

type FoldLike' r s a = LensLike' (Constant r :: Type -> Type) s a #

data Constant a (b :: k) :: forall k. Type -> k -> Type #

Constant functor.

Instances
Bitraversable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Constant a b -> f (Constant c d) #

Bifoldable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bifold :: Monoid m => Constant m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Constant a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Constant a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Constant a b -> c #

Bifunctor (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bimap :: (a -> b) -> (c -> d) -> Constant a c -> Constant b d #

first :: (a -> b) -> Constant a c -> Constant b c #

second :: (b -> c) -> Constant a b -> Constant a c #

Eq2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Constant a c -> Constant b d -> Bool #

Ord2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Constant a c -> Constant b d -> Ordering #

Read2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Constant a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Constant a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Constant a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Constant a b] #

Show2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Constant a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Constant a b] -> ShowS #

Functor (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

fmap :: (a0 -> b) -> Constant a a0 -> Constant a b #

(<$) :: a0 -> Constant a b -> Constant a a0 #

Monoid a => Applicative (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

pure :: a0 -> Constant a a0 #

(<*>) :: Constant a (a0 -> b) -> Constant a a0 -> Constant a b #

liftA2 :: (a0 -> b -> c) -> Constant a a0 -> Constant a b -> Constant a c #

(*>) :: Constant a a0 -> Constant a b -> Constant a b #

(<*) :: Constant a a0 -> Constant a b -> Constant a a0 #

Foldable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

fold :: Monoid m => Constant a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Constant a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

toList :: Constant a a0 -> [a0] #

null :: Constant a a0 -> Bool #

length :: Constant a a0 -> Int #

elem :: Eq a0 => a0 -> Constant a a0 -> Bool #

maximum :: Ord a0 => Constant a a0 -> a0 #

minimum :: Ord a0 => Constant a a0 -> a0 #

sum :: Num a0 => Constant a a0 -> a0 #

product :: Num a0 => Constant a a0 -> a0 #

Traversable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

traverse :: Applicative f => (a0 -> f b) -> Constant a a0 -> f (Constant a b) #

sequenceA :: Applicative f => Constant a (f a0) -> f (Constant a a0) #

mapM :: Monad m => (a0 -> m b) -> Constant a a0 -> m (Constant a b) #

sequence :: Monad m => Constant a (m a0) -> m (Constant a a0) #

Contravariant (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

contramap :: (a0 -> b) -> Constant a b -> Constant a a0 #

(>$) :: b -> Constant a b -> Constant a a0 #

Eq a => Eq1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq :: (a0 -> b -> Bool) -> Constant a a0 -> Constant a b -> Bool #

Ord a => Ord1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare :: (a0 -> b -> Ordering) -> Constant a a0 -> Constant a b -> Ordering #

Read a => Read1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Constant a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Constant a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Constant a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Constant a a0] #

Show a => Show1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Constant a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Constant a a0] -> ShowS #

Phantom (Constant a :: Type -> Type) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Eq a => Eq (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

(==) :: Constant a b -> Constant a b -> Bool #

(/=) :: Constant a b -> Constant a b -> Bool #

Ord a => Ord (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

compare :: Constant a b -> Constant a b -> Ordering #

(<) :: Constant a b -> Constant a b -> Bool #

(<=) :: Constant a b -> Constant a b -> Bool #

(>) :: Constant a b -> Constant a b -> Bool #

(>=) :: Constant a b -> Constant a b -> Bool #

max :: Constant a b -> Constant a b -> Constant a b #

min :: Constant a b -> Constant a b -> Constant a b #

Read a => Read (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Show a => Show (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

showsPrec :: Int -> Constant a b -> ShowS #

show :: Constant a b -> String #

showList :: [Constant a b] -> ShowS #

Semigroup a => Semigroup (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

(<>) :: Constant a b -> Constant a b -> Constant a b #

sconcat :: NonEmpty (Constant a b) -> Constant a b #

stimes :: Integral b0 => b0 -> Constant a b -> Constant a b #

Monoid a => Monoid (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

mempty :: Constant a b #

mappend :: Constant a b -> Constant a b -> Constant a b #

mconcat :: [Constant a b] -> Constant a b #

class Functor f => Phantom (f :: Type -> Type) #

Minimal complete definition

coerce

Instances
Phantom (Const a :: Type -> Type) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Const a a0 -> Const a b

Phantom f => Phantom (AlongsideLeft f a) 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: AlongsideLeft f a a0 -> AlongsideLeft f a b

Phantom f => Phantom (AlongsideRight f a) 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: AlongsideRight f a a0 -> AlongsideRight f a b

Phantom g => Phantom (FromG e g) 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: FromG e g a -> FromG e g b

Phantom f => Phantom (Backwards f) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Backwards f a -> Backwards f b

Phantom (Constant a :: Type -> Type) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Phantom g => Phantom (FromF i j g) 
Instance details

Defined in Lens.Family.Stock

Methods

coerce :: FromF i j g a -> FromF i j g b

(Phantom f, Functor g) => Phantom (Compose f g) 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Compose f g a -> Compose f g b

class (Traversable f, Applicative f) => Identical (f :: Type -> Type) #

Minimal complete definition

extract

Instances
Identical Identity 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Identity a -> a

Identical f => Identical (Backwards f) 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Backwards f a -> a

(Identical f, Identical g) => Identical (Compose f g) 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Compose f g a -> a