lens-family-core-1.2.0: Haskell 98 Lens Families

Safe HaskellSafe-Inferred
LanguageHaskell98

Lens.Family

Contents

Description

This is the main module for end-users of lens-families-core. If you are not building your own lenses or traversals, but just using functional references 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 => (b -> f b) -> a -> f a and lens families have type Functor f => (b i -> f (b j)) -> a i -> f (a 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 b => LensLike' Maybe a b -> (b -> b) -> a -> a
sharedUpdate l f a = fromMaybe a (l f' a)
 where
  f' b | fb == b  = Nothing
       | otherwise = Just fb
   where
    fb = f b

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.

Like lenses, 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 => (b -> f b) -> a -> f a and traversal families have type Applicative f => (b i -> f (b j)) -> a i -> f (a j).

For stock lenses and traversals, see Lens.Family.Stock.

To build your own lenses and traversals, see Lens.Family.Unchecked.

References:

Documentation

to :: Phantom f => (a -> b) -> LensLike f a a' b b' Source

to :: (a -> b) -> Getter a a' b b'

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 b a a' b b' -> a -> b Source

view :: Getter a a' b b' -> a -> b

Demote a lens or getter to a projection function.

view :: Monoid b => Fold a a' b b' -> a -> b

Returns the monoidal summary of a traversal or a fold.

(^.) :: a -> FoldLike b a a' b b' -> b infixl 8 Source

(^.) :: a -> Getter a a' b b' -> b

Access the value referenced by a getter or lens.

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

Access the monoidal summary referenced by a getter or lens.

folding :: (Foldable g, Phantom f, Applicative f) => (a -> g b) -> LensLike f a a' b b' Source

folding :: (a -> [b]) -> Fold a a' b b'

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 a a' b b' -> (b -> r) -> a -> r Source

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

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

views :: Getter a a' b b' -> (b -> r) -> a -> 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 a = f (view l a)

(^..) :: a -> FoldLike [b] a a' b b' -> [b] infixl 8 Source

(^..) :: a -> Getter a a' b b' -> [b]

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

(^?) :: a -> FoldLike (First b) a a' b b' -> Maybe b infixl 8 Source

(^?) :: a -> Fold a a' b b' -> Maybe b

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

toListOf :: FoldLike [b] a a' b b' -> a -> [b] Source

toListOf :: Fold a a' b b' -> a -> [b]

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

allOf :: FoldLike All a a' b b' -> (b -> Bool) -> a -> Bool Source

allOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool

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

anyOf :: FoldLike Any a a' b b' -> (b -> Bool) -> a -> Bool Source

anyOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool

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

firstOf :: FoldLike (First b) a a' b b' -> a -> Maybe b Source

firstOf :: Fold a a' b b' -> a -> Maybe b

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

lastOf :: FoldLike (Last b) a a' b b' -> a -> Maybe b Source

lastOf :: Fold a a' b b' -> a -> Maybe b

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

sumOf :: Num b => FoldLike (Sum b) a a' b b' -> a -> b Source

sumOf :: Num b => Fold a a' b b' -> a -> b

Returns the sum of all the referenced values.

productOf :: Num b => FoldLike (Product b) a a' b b' -> a -> b Source

productOf :: Num b => Fold a a' b b' -> a -> b

Returns the product of all the referenced values.

lengthOf :: Num r => FoldLike (Sum r) a a' b b' -> a -> r Source

lengthOf :: Num r => Fold a a' b b' -> a -> r

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

nullOf :: FoldLike All a a' b b' -> a -> Bool Source

nullOf :: Fold a a' b b' -> a -> Bool

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

backwards :: LensLike (Backwards f) a a' b b' -> LensLike f a a' b b' Source

backwards :: Traversal a a' b b' -> Traversal a a' b b'
backwards :: Fold a a' b b' -> Fold a a' b b'

Given a traversal or fold, reverse the order that elements are traversed.

backwards :: Lens a a' b b' -> Lens a a' b b'
backwards :: Getter a a' b b' -> Getter a a' b b'
backwards :: Setter a a' b b' -> Setter a a' b b'

No effect on lenses, getters or setters.

over :: ASetter a a' b b' -> (b -> b') -> a -> a' Source

Demote a setter to a semantic editor combinator.

(%~) :: ASetter a a' b b' -> (b -> b') -> a -> a' infixr 4 Source

Modify all referenced fields.

set :: ASetter a a' b b' -> b' -> a -> a' Source

Set all referenced fields to the given value.

(.~) :: ASetter a a' b b' -> b' -> a -> a' infixr 4 Source

Set all referenced fields to the given value.

(&) :: a -> (a -> b) -> b infixl 1 Source

A flipped version of ($).

Pseudo-imperatives

(+~) :: Num b => ASetter' a b -> b -> a -> a infixr 4 Source

(*~) :: Num b => ASetter' a b -> b -> a -> a infixr 4 Source

(-~) :: Num b => ASetter' a b -> b -> a -> a infixr 4 Source

(//~) :: Fractional b => ASetter' a b -> b -> a -> a infixr 4 Source

(&&~) :: ASetter' a Bool -> Bool -> a -> a infixr 4 Source

(||~) :: ASetter' a Bool -> Bool -> a -> a infixr 4 Source

(<>~) :: Monoid o => ASetter' a o -> o -> a -> a infixr 4 Source

Monoidally append a value to all referenced fields.

Types

type LensLike f a a' b b' = (b -> f b') -> a -> f a' Source

type LensLike' f a b = (b -> f b) -> a -> f a Source

type FoldLike r a a' b b' = LensLike (Constant r) a a' b b' Source

type FoldLike' r a b = LensLike' (Constant r) a b Source

type ASetter a a' b b' = LensLike Identity a a' b b' Source

class Functor f => Phantom f Source

Minimal complete definition

coerce

data Constant a b :: * -> * -> *

Constant functor.

Re-exports

class Functor f => Applicative f

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

A minimal complete definition must include implementations of these functions satisfying the following laws:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

class Foldable t

Data structures that can be folded.

Minimal complete definition: foldMap or foldr.

For example, given a data type

data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)

a suitable instance would be

instance Foldable Tree where
   foldMap f Empty = mempty
   foldMap f (Leaf x) = f x
   foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r

This is suitable even for abstract types, as the monoid is assumed to satisfy the monoid laws. Alternatively, one could define foldr:

instance Foldable Tree where
   foldr f z Empty = z
   foldr f z (Leaf x) = f x z
   foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l

Minimal complete definition

foldMap | foldr

class Monoid a

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Minimal complete definition: mempty and mappend.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Instances

Monoid Ordering 
Monoid () 
Monoid All 
Monoid Any 
Monoid IntSet 
Monoid [a] 
Monoid a => Monoid (Dual a) 
Monoid (Endo a) 
Num a => Monoid (Sum a) 
Num a => Monoid (Product a) 
Monoid (First a) 
Monoid (Last a) 
Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Monoid (IntMap a) 
Ord a => Monoid (Set a) 
Monoid b => Monoid (a -> b) 
(Monoid a, Monoid b) => Monoid (a, b) 
Monoid a => Monoid (Const a b) 
Monoid (Proxy * s) 
Ord k => Monoid (Map k v) 
Typeable (* -> Constraint) Monoid 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

data Backwards f a :: (* -> *) -> * -> *

The same functor, but with an Applicative instance that performs actions in the reverse order.

Instances

Alternative f => Alternative (Backwards f)

Try alternatives in the same order as f.

Functor f => Functor (Backwards f)

Derived instance.

Applicative f => Applicative (Backwards f)

Apply f-actions in the reverse order.

Foldable f => Foldable (Backwards f)

Derived instance.

Traversable f => Traversable (Backwards f)

Derived instance.

Phantom f => Phantom (Backwards f) 
Identical f => Identical (Backwards f) 

data All :: *

Boolean monoid under conjunction.

Instances

Bounded All 
Eq All 
Ord All 
Read All 
Show All 
Generic All 
Monoid All 
type Rep All = D1 D1All (C1 C1_0All (S1 S1_0_0All (Rec0 Bool))) 

data Any :: *

Boolean monoid under disjunction.

Instances

Bounded Any 
Eq Any 
Ord Any 
Read Any 
Show Any 
Generic Any 
Monoid Any 
type Rep Any = D1 D1Any (C1 C1_0Any (S1 S1_0_0Any (Rec0 Bool))) 

data First a :: * -> *

Maybe monoid returning the leftmost non-Nothing value.

Instances

Generic1 First 
Eq a => Eq (First a) 
Ord a => Ord (First a) 
Read a => Read (First a) 
Show a => Show (First a) 
Generic (First a) 
Monoid (First a) 
type Rep1 First = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec1 Maybe))) 
type Rep (First a) = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec0 (Maybe a)))) 

data Last a :: * -> *

Maybe monoid returning the rightmost non-Nothing value.

Instances

Generic1 Last 
Eq a => Eq (Last a) 
Ord a => Ord (Last a) 
Read a => Read (Last a) 
Show a => Show (Last a) 
Generic (Last a) 
Monoid (Last a) 
type Rep1 Last = D1 D1Last (C1 C1_0Last (S1 S1_0_0Last (Rec1 Maybe))) 
type Rep (Last a) = D1 D1Last (C1 C1_0Last (S1 S1_0_0Last (Rec0 (Maybe a)))) 

data Sum a :: * -> *

Monoid under addition.

Instances

Generic1 Sum 
Bounded a => Bounded (Sum a) 
Eq a => Eq (Sum a) 
Num a => Num (Sum a) 
Ord a => Ord (Sum a) 
Read a => Read (Sum a) 
Show a => Show (Sum a) 
Generic (Sum a) 
Num a => Monoid (Sum a) 
type Rep1 Sum = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum Par1)) 
type Rep (Sum a) = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum (Rec0 a))) 

data Product a :: * -> *

Monoid under multiplication.

Instances

Generic1 Product 
Bounded a => Bounded (Product a) 
Eq a => Eq (Product a) 
Num a => Num (Product a) 
Ord a => Ord (Product a) 
Read a => Read (Product a) 
Show a => Show (Product a) 
Generic (Product a) 
Num a => Monoid (Product a) 
type Rep1 Product = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product Par1)) 
type Rep (Product a) = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product (Rec0 a)))