lens-0.4: Lenses and Lens Families

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe

Control.Lens

Contents

Description

This package provides lenses that are compatible with other van Laarhoven lens libraries, while reducing the complexty of the imports.

Lenses produced by this library are compatible with other van Laarhoven lens family libraries, such as lens-family, lens-family-core and lens-family-th, but the API is simpler.

Note: If you merely want your library to _provide_ lenses you may not have to actually import _any_ lens library, for a Lens Bar Foo, just export a function with the signature:

 foo :: Functor f => (Foo -> f Foo) -> Bar -> f Bar

and then you can compose it with other lenses using (.).

This package provides lenses, lens families, setters, setter families, getters, traversals, folds, and traversal families in such a way that they can all be composed automatically with (.).

You can derive lenses automatically for many data types:

 import Control.Lens.TH
 data Foo a = Foo { _fooArgs :: [String], _fooValue :: a }
 makeLenses ''Foo

This defines the following lenses:

 fooArgs :: Lens (Foo a) [String]
 fooValue :: LensFamily (Foo a) (Foo b) a b

Synopsis

Lenses

type Lens a b = forall f. Functor f => (b -> f b) -> a -> f aSource

A Lens is a purely functional reference to part of a data structure. It can be used to read or write to that part of the whole.

With great power comes great responsibility, and a Lens is subject to the lens laws:

 reading l (writing l b a)   = b
 writing l (reading l a) a   = a
 writing l c (writing l b a) = writing l c a

Every Lens can be used directly as a LensFamily or as a Getter, Setter, or Traversal, which transitively mens it can be used as almost anything! Such as a TraversalFamily, a GetterFamily, a FoldFamily, a Fold, or a SetterFamily.

Example:

 import Data.Complex
 imaginary :: Lens (Complex a) a
 imaginary f (e :+ i) = (e :+) <$> f i
 type Lens a b             = LensFamily a a b b

type LensFamily a b c d = forall f. Functor f => (c -> f d) -> a -> f bSource

A LensFamily is a more general form of a Lens that permits polymorphic field updates

With great power comes great responsibility, and a LensFamily is subject to the lens laws:

 reading l (writing l b a)   = b
 writing l (reading l a) a   = a
 writing l c (writing l b a) = writing l c a

These laws are strong enough that the 4 type parameters of a LensFamily cannot vary fully independently. For more on how they interact, read the Why is it a Lens Family? section of http://comonad.com/reader/2012/mirrored-lenses/.

Every LensFamily can be used as a GetterFamily, a SetterFamily or a TraversalFamily, which transitively means it can be used as a FoldFamily.

Despite the complicated signature the pattern for implementing a LensFamily is the same as a Lens. in fact the implementation doesn't change, the type signature merely generalizes.

 identity :: LensFamily (Identity a) (Identity b) a b
 identity f (Identity a) = Identity <$> f a

Constructing Lenses

lens :: (a -> c) -> (d -> a -> b) -> LensFamily a b c dSource

Build a Lens or LensFamily from a getter and a setter.

 lens :: Functor f => (a -> c) -> (d -> a -> b) -> (c -> f d) -> a -> f b

iso :: (a -> c) -> (d -> b) -> LensFamily a b c dSource

Built a Lens or LensFamily from an isomorphism or an isomorphism family

 iso :: Functor f => (a -> c) -> (d -> b) -> (c -> f d) -> a -> f b

clone :: Functor f => ((c -> IndexedStore c d d) -> a -> IndexedStore c d b) -> (c -> f d) -> a -> f bSource

Cloning a Lens or LensFamily is one way to make sure you arent given something weaker, such as a Traversal or TraversalFamily, and can be used as a way to pass around lenses that have to be monomorphic in f.

Getters

type Getter a b = forall z. (b -> Const z b) -> a -> Const z aSource

A Getter can be used directly as a GetterFamily or as a Fold, and hence it can be as a FoldFamily.

In general while your combinators may produce a Getter it is better to consume any GetterFamily.

 type Getter a b           = GetterFamily a a b b

type GetterFamily a b c d = forall z. (c -> Const z d) -> a -> Const z bSource

A GetterFamily describes how to retrieve a single value in a way that can be composed with other lens-like constructions. It can be used directly as a FoldFamily, since it just ignores the Monoid.

getting :: (a -> c) -> GetterFamily a b c dSource

Build a Getter or GetterFamily

Getting Values

reading :: ((c -> Const c d) -> a -> Const c b) -> a -> cSource

Get the value of a Getter, Lens or LensFamily or the fold of a Fold, Traversal or TraversalFamily that points at monoidal values.

 reading :: GetterFamily a b c d -> a -> c

(^.) :: a -> ((c -> Const c d) -> a -> Const c b) -> cSource

Read a field from a Getter, Lens or LensFamily. The fixity and semantics are such that subsequent field accesses can be performed with (Prelude..) This is the same operation as 'flip reading'

 ghci> ((0, 1 :+ 2), 3)^._1._2.getting magnitude
 2.23606797749979

(^$) :: ((c -> Const c d) -> a -> Const c b) -> a -> cSource

Read the value of a Getter, Lens or LensFamily. This is the same operation as reading.

Setters

type Setter a b = (b -> Identity b) -> a -> Identity aSource

Every Setter can be used directly as a SetterFamily.

Note: the only lens law that applies to a Setter is

 writing l c (writing l b a) = writing l c a

reading a Setter doesn't work in general, so the other two laws can never be invoked.

 type Setter a b                = SetterFamily a a b b

type SetterFamily a b c d = (c -> Identity d) -> a -> Identity bSource

A SetterFamily describes a way to perform polymorphic update to potentially multiple fields in a way that can be composed with other lens-like constructions that can be used as a SetterFamily.

The typical way to obtain a SetterFamily is to build one with setting or to compose some other Lens-like construction with a SetterFamily.

Note: the only lens law that applies to a SetterFamily is

 writing l c (writing l b a) = writing l c a

reading a SetterFamily doesn't work in general, so the other two laws can never be invoked.

setting :: ((c -> d) -> a -> b) -> SetterFamily a b c dSource

Build a Setter or SetterFamily

 setting . modifying = id
 modifying . setting = id

Setting Values

modifying :: SetterFamily a b c d -> (c -> d) -> a -> bSource

Modify the target of a Lens, LensFamily or all the targets of a Traversal, TraversalFamily, Setter or SetterFamily

 fmap = modifying traverse
 setting . modifying = id
 modifying . setting = id
 modifying :: ((c -> Identity d) -> a -> Identity b) -> (c -> d) -> a -> b

writing :: SetterFamily a b c d -> d -> a -> bSource

Replace the target of a Lens, LensFamily, Setter or SetterFamily

 (<$) = writing traverse
 writing :: ((c -> Identity d) -> a -> Identity b) -> d -> a -> b

(^%=) :: SetterFamily a b c d -> (c -> d) -> a -> bSource

Modifies the target of a Lens, LensFamily, Setter, or SetterFamily.

This is an infix version of modifying

 fmap f = traverse ^%= f
 (^%=) :: ((c -> Identity d) -> a -> Identity b) -> (c -> d) -> a -> b

(^=) :: SetterFamily a b c d -> d -> a -> bSource

Replaces the target(s) of a Lens, LensFamily, Setter or SetterFamily.

This is an infix version of writing

 f <$ a = traverse ^= f $ a
 (^=) :: ((c -> Identity d) -> a -> Identity b) -> d -> a -> b

(^+=) :: Num c => Setter a c -> c -> a -> aSource

Increment the target(s) of a numerically valued Lens or Setter'

 ghci> _1 ^+= 1 $ (1,2)
 (2,2)
 (^+=) :: Num c => ((c -> Identity c) -> a -> Identity a) -> c -> a -> a

(^-=) :: Num c => Setter a c -> c -> a -> aSource

Decrement the target(s) of a numerically valued Lens or Setter

 ghci> _1 ^-= 2 $ (1,2)
 (-1,2)
 (^-=) :: ((c -> Identity c) -> a -> Identity a) -> c -> a -> a

(^*=) :: Num c => Setter a c -> c -> a -> aSource

Multiply the target(s) of a numerically valued Lens or Setter'

 ghci> _2 ^*= 4 $ (1,2)
 (1,8)
 (^*=) :: Num c => ((c -> Identity c) -> a -> Identity a) -> c -> a -> a

(^/=) :: Fractional b => Setter a b -> b -> a -> aSource

Divide the target(s) of a numerically valued Setter

 (^/=) :: Fractional c => ((c -> Identity c) -> a -> Identity a) -> c -> a -> a

(^||=) :: Setter a Bool -> Bool -> a -> aSource

Logically || the target(s) of a Bool-valued Lens or Setter

 (^||=):: ((Bool -> Identity Bool) -> a -> Identity a) -> Bool -> a -> a

(^&&=) :: Setter a Bool -> Bool -> a -> aSource

Logically && the target(s) of a Bool-valued Lens or Setter (^&&=) :: ((Bool -> Identity Bool) -> a -> Identity a) -> Bool -> a -> a

Manipulating State

access :: MonadState a m => ((c -> Const c d) -> a -> Const c b) -> m cSource

Access a field of a state monad

(%=) :: MonadState a m => Setter a b -> (b -> b) -> m ()Source

Modify the value of a field in our monadic state

(~=) :: MonadState a m => Setter a b -> b -> m ()Source

Set the value of a field in our monadic state

(+=) :: (MonadState a m, Num b) => Setter a b -> b -> m ()Source

Modify a numeric field in our monadic state by adding to it

(-=) :: (MonadState a m, Num b) => Setter a b -> b -> m ()Source

Modify a numeric field in our monadic state by subtracting from it

(*=) :: (MonadState a m, Num b) => Setter a b -> b -> m ()Source

Modify a numeric field in our monadic state by multiplying it

(//=) :: (MonadState a m, Fractional b) => Setter a b -> b -> m ()Source

Modify a numeric field in our monadic state by dividing it

(||=) :: MonadState a m => Setter a Bool -> Bool -> m ()Source

Modify a boolean field in our monadic state by computing its logical || with another value.

(&&=) :: MonadState a m => Setter a Bool -> Bool -> m ()Source

Modify a boolean field in our monadic state by computing its logical && with another value.

(%%=) :: MonadState a m => ((b -> (c, b)) -> a -> (c, a)) -> (b -> (c, b)) -> m cSource

Modify the value of a field in our monadic state and return some information about it

class Focus st whereSource

This class allows us to use focus on a number of different monad transformers.

Methods

focus :: Monad m => ((b -> Focusing m c b) -> a -> Focusing m c a) -> st b m c -> st a m cSource

Use a lens to lift an operation with simpler context into a larger context

Instances

Focus ReaderT

We can focus Reader environments, too!

Focus StateT 
Focus StateT 

Folds

type Fold a b = forall m. Monoid m => (b -> Const m b) -> a -> Const m aSource

Every Fold can be used directly as a FoldFamily (and you should probably be using a FoldFamily instead.)

 type Fold a b           = FoldFamily a b c d

type FoldFamily a b c d = forall m. Monoid m => (c -> Const m d) -> a -> Const m bSource

A FoldFamily describes how to retrieve multiple values in a way that can be composed with other lens-like constructions.

A FoldFamily a b c d provides a structure with operations very similar to those of the Foldable typeclass, see foldMapOf and the other FoldFamily combinators.

By convention, if there exists a foo method that expects a Foldable (f c), then there should be a fooOf method that takes a FoldFamily a b c d and a value of type a.

Common Folds

folded :: Foldable f => FoldFamily (f c) b c dSource

Obtain a FoldFamily from any Foldable

folding :: Foldable f => (a -> f c) -> FoldFamily a b c dSource

Building a FoldFamily

Fold Combinators

foldMapOf :: Monoid m => ((c -> Const m d) -> a -> Const m b) -> (c -> m) -> a -> mSource

 foldMap = foldMapOf folded
 foldMapOf :: Monoid m => FoldFamily a b c d -> (c -> m) -> a -> m

foldrOf :: ((c -> Const (Endo e) d) -> a -> Const (Endo e) b) -> (c -> e -> e) -> e -> a -> eSource

 foldr = foldrOf folded
 foldrOf :: FoldFamily a b c d -> (c -> e -> e) -> e -> a -> e

foldOf :: Monoid m => ((m -> Const m d) -> a -> Const m b) -> a -> mSource

 fold = foldOf folded
 foldOf :: Monoid m => FoldFamily a b m d -> a -> m

toListOf :: ((c -> Const [c] d) -> a -> Const [c] b) -> a -> [c]Source

 toList = toListOf folded
 toListOf :: FoldFamily a b c d -> a -> [c]

anyOf :: ((c -> Const Any d) -> a -> Const Any b) -> (c -> Bool) -> a -> BoolSource

 any = anyOf folded
 anyOf :: FoldFamily a b c d -> (c -> Bool) -> a -> Bool

allOf :: ((c -> Const All d) -> a -> Const All b) -> (c -> Bool) -> a -> BoolSource

 all = allOf folded
 allOf :: FoldFamily a b c d -> (c -> Bool) -> a -> Bool

andOf :: ((Bool -> Const All d) -> a -> Const All b) -> a -> BoolSource

 and = andOf folded
 andOf :: FoldFamily a b Bool d -> a -> Bool

orOf :: ((Bool -> Const Any d) -> a -> Const Any b) -> a -> BoolSource

 or = orOf folded
 orOf :: FoldFamily a b Bool d -> a -> Bool

productOf :: Num c => ((c -> Const (Product c) d) -> a -> Const (Product c) b) -> a -> cSource

 product = productOf folded
 productOf ::  Num c => FoldFamily a b c d -> a -> c

sumOf :: Num c => ((c -> Const (Sum c) d) -> a -> Const (Sum c) b) -> a -> cSource

 sum = sumOf folded
 sumOf ::  Num c => FoldFamily a b c d -> a -> c

traverseOf_ :: Applicative f => ((c -> Const (Traversed f) d) -> a -> Const (Traversed f) b) -> (c -> f e) -> a -> f ()Source

 traverse_ = traverseOf_ folded
 traverseOf_ :: Applicative f => FoldFamily a b c d -> (c -> f e) -> a -> f ()

forOf_ :: Applicative f => ((c -> Const (Traversed f) d) -> a -> Const (Traversed f) b) -> a -> (c -> f e) -> f ()Source

 for_ = forOf_ folded
 forOf_ :: Applicative f => FoldFamily a b c d -> a -> (c -> f e) -> f ()

sequenceAOf_ :: Applicative f => ((f () -> Const (Traversed f) d) -> a -> Const (Traversed f) b) -> a -> f ()Source

 sequenceA_ = sequenceAOf_ folded
 sequenceAOf_ :: Applicative f => FoldFamily a b (f ()) d -> a -> f ()

mapMOf_ :: Monad m => ((c -> Const (Traversed (WrappedMonad m)) d) -> a -> Const (Traversed (WrappedMonad m)) b) -> (c -> m e) -> a -> m ()Source

 mapM_ = mapMOf_ folded
 mapMOf_ :: Monad m => FoldFamily a b c d -> (c -> m e) -> a -> m ()

forMOf_ :: Monad m => ((c -> Const (Traversed (WrappedMonad m)) d) -> a -> Const (Traversed (WrappedMonad m)) b) -> a -> (c -> m e) -> m ()Source

 forM_ = forMOf_ folded
 forMOf_ :: Monad m => FoldFamily a b c d -> a -> (c -> m e) -> m ()

sequenceOf_ :: Monad m => ((m c -> Const (Traversed (WrappedMonad m)) d) -> a -> Const (Traversed (WrappedMonad m)) b) -> a -> m ()Source

 sequence_ = sequenceOf_ folded
 sequenceOf_ :: Monad m => FoldFamily a b (m b) d -> a -> m ()

asumOf :: Alternative f => ((f c -> Const (Endo (f c)) d) -> a -> Const (Endo (f c)) b) -> a -> f cSource

The sum of a collection of actions, generalizing concatOf.

 asum = asumOf folded
 asumOf :: Alternative f => FoldFamily a b c d -> a -> f c

msumOf :: MonadPlus m => ((m c -> Const (Endo (m c)) d) -> a -> Const (Endo (m c)) b) -> a -> m cSource

The sum of a collection of actions, generalizing concatOf.

 msum = msumOf folded
 msumOf :: MonadPlus m => FoldFamily a b c d -> a -> m c

concatMapOf :: ((c -> Const [e] d) -> a -> Const [e] b) -> (c -> [e]) -> a -> [e]Source

 concatMap = concatMapOf folded
 concatMapOf :: FoldFamily a b c d -> (c -> [e]) -> a -> [e]

concatOf :: (([e] -> Const [e] d) -> a -> Const [e] b) -> a -> [e]Source

 concat = concatOf folded
 concatOf :: FoldFamily a b [e] d -> a -> [e]

elemOf :: Eq c => ((c -> Const Any d) -> a -> Const Any b) -> c -> a -> BoolSource

 elem = elemOf folded
 elemOf :: Eq c => FoldFamily a b c d -> c -> a -> Bool

notElemOf :: Eq c => ((c -> Const Any d) -> a -> Const Any b) -> c -> a -> BoolSource

 notElem = notElemOf folded
 notElemOf :: Eq c => FoldFamily a b c d -> c -> a -> Bool

Traversals

type Traversal a b = forall f. Applicative f => (b -> f b) -> a -> f aSource

Every Traversal can be used as a TraversalFamily or a Setter or Fold, so it can transitively be used as a FoldFamily or SetterFamily as well.

 type Traversal a b             = TraversalFamily a a b b

type TraversalFamily a b c d = forall f. Applicative f => (c -> f d) -> a -> f bSource

A TraversalFamily can be used directly as a SetterFamily or a FoldFamily and provides the ability to both read and update multiple fields, subject to the (relatively weak) TraversalFamily laws.

These are also known as MultiLens families, but they have the signature and spirit of

 traverse :: Traversable f => TraversalFamiy (f a) (f b) a b

and the more evocative name suggests their application.

Common Traversals

traverseNothing :: TraversalFamily a a c dSource

This is the traversal that never succeeds at returning any values

 traverseNothing :: Applicative f => (c -> f d) -> a -> f a

traverseValueAt :: Ord k => k -> Traversal (Map k v) vSource

Traverse the value at a given key in a Map

 traverseValueAt :: (Applicative f, Ord k) => k -> (v -> f v) -> Map k v -> f (Map k v)
 traverseValueAt k = valueAt k . traverse

traverseValueAtInt :: Int -> Traversal (IntMap v) vSource

Traverse the value at a given key in an IntMap

 traverseValueAtInt :: Applicative f => Int -> (v -> f v) -> IntMap v -> f (IntMap v)
 traverseValueAtInt k = valueAtInt k . traverse

traverseHead :: Traversal [a] aSource

 traverseHead :: Applicative f => (a -> f a) -> [a] -> f [a]

traverseTail :: Traversal [a] [a]Source

 traverseTail :: Applicative f => ([a] -> f [a]) -> [a] -> f [a]

traverseLeft :: TraversalFamily (Either a c) (Either b c) a bSource

A traversal for tweaking the left-hand value in an Either:

 traverseLeft :: Applicative f => (a -> f b) -> Either a c -> f (Either b c)

traverseRight :: TraversalFamily (Either c a) (Either c b) a bSource

traverse the right-hand value in an Either:

 traverseRight :: Applicative f => (a -> f b) -> Either c a -> f (Either c a)
 traverseRight = traverse

Unfortunately the instance for 'Traversable (Either c)' is still missing from base, so this can't just be traverse

traverseElement :: Traversable t => Int -> Traversal (t a) aSource

Traverse a single element in a traversable container.

 traverseElement :: (Applicative f, Traversable t) => Int -> (a -> f a) -> t a -> f (t a)

class TraverseByteString t whereSource

Methods

traverseByteString :: Traversal t Word8Source

Traverse the individual bytes in a ByteString

 anyOf traverseByteString (==0x80) :: TraverseByteString b => b -> Bool

Traversal Combinators

traverseOf :: Applicative f => ((c -> f d) -> a -> f b) -> (c -> f d) -> a -> f bSource

 traverseOf = id
 traverse = traverseOf traverse
 traverseOf :: Applicative f => TraversalFamily a b c d -> (c -> f d) -> a -> f b

mapMOf :: Monad m => ((c -> WrappedMonad m d) -> a -> WrappedMonad m b) -> (c -> m d) -> a -> m bSource

 mapM = mapMOf traverse
 mapMOf :: Monad m => TraversalFamily a b c d -> (c -> m d) -> a -> m b

sequenceAOf :: Applicative f => ((f c -> f (f c)) -> a -> f b) -> a -> f bSource

 sequenceA = sequenceAOf traverse
 sequenceAOf :: Applicative f => TraversalFamily a b (f c) (f c) -> a -> f b

sequenceOf :: Monad m => ((m c -> WrappedMonad m (m c)) -> a -> WrappedMonad m b) -> a -> m bSource

 sequence = sequenceOf traverse
 sequenceOf :: Monad m => TraversalFamily a b (m c) (m c) -> a -> m b

Common Lenses

_1 :: LensFamily (a, c) (b, c) a bSource

This is a lens family that can change the value (and type) of the first field of a pair.

_2 :: LensFamily (c, a) (c, b) a bSource

As _1, but for the second field of a pair.

valueAt :: Ord k => k -> Lens (Map k v) (Maybe v)Source

This lens can be used to read, write or delete a member of a Map.

 ghci> Map.fromList [("hello",12)] ^. valueAt "hello"
 Just 12

valueAtInt :: Int -> Lens (IntMap v) (Maybe v)Source

This lens can be used to read, write or delete a member of an IntMap.

 ghci> IntMap.fromList [(1,"hello")]  ^. valueAt 1
 Just "hello"
 ghci> valueAt 2 ^= "goodbye" $ IntMap.fromList [(1,"hello")]
 fromList [(1,"hello"),(2,"goodbye")]

contains :: Ord k => k -> Lens (Set k) BoolSource

This lens can be used to read, write or delete a member of a Set

 ghci> contains 3 ^= False $ Set.fromList [1,2,3,4]
 fromList [1,2,4]

containsInt :: Int -> Lens IntSet BoolSource

This lens can be used to read, write or delete a member of an IntSet

 ghci> containsInt 3 ^= False $ IntSet.fromList [1,2,3,4]
 fromList [1,2,4]

identity :: LensFamily (Identity a) (Identity b) a bSource

This lens can be used to access the contents of the Identity monad

resultAt :: Eq e => e -> Lens (e -> a) aSource

This lens can be used to change the result of a function but only where the arguments match the key given.

Implementation details

data IndexedStore c d a Source

Instances

data Focusing m c a Source

Instances

Monad m => Functor (Focusing m c) 
(Monad m, Monoid c) => Applicative (Focusing m c) 

data Traversed f Source

Instances