lens-0.3: Lenses and Lens Families

PortabilityRankNTypes, TemplateHaskell
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

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, multilenses, multi-getters, and multi-lens families in such a way that they can all be composed automatically with (.).

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 MultiLens, which transitively mens it can be used as almost anything! Such as a MultiLensFamily, a GetterFamily, a MultiGetterFamily, a MultiGetter, or a SetterFamily.

 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 MultiLensFamily, which transitively means it can be used as a MultiGetterFamily.

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.

 sndL :: LensFamily (c,a) (c,b) a b
 sndL f (a,c) = (,) a <$> f c

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 MultiGetter, and hence it can be as a MutliGetterFamily.

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 Setter a b = (b -> Identity b) -> a -> Identity aSource

Every Setter can be used directly as a SetterFamily.

 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

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

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

Every MultiLens can be used as a MultiLensFamily or a Setter or MultiGetter, so it can transitively be used as a MultiGetterFamily or SetterFamily as well.

 type MultiLens a b             = MultiLensFamily a a b b

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

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

Constructing Lenses

makeLenses :: Name -> Q [Dec]Source

Derive lenses for the record selectors in a single-constructor data declaration, or for the record selector in a newtype declaration. Lenses will only be generated for record fields which are prefixed with an underscore.

Example usage:

 makeLenses ''Foo

makeLensesBySource

Arguments

:: (String -> Maybe String)

the name transformer

-> Name 
-> Q [Dec] 

Derive lenses with the provided name transformation and filtering function. Produce Just lensName to generate a lens of the resultant name, or Nothing to not generate a lens for the input record name.

Example usage:

 makeLensesBy (\n -> Just (n ++ "L")) ''Foo

makeLensesFor :: [(String, String)] -> Name -> Q [Dec]Source

Derive lenses, specifying explicit pairings of (fieldName, lensName).

Example usage:

 makeLensesFor [("_foo", "fooLens"), ("bar", "lbar")] ''Foo

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 MultiLens or MultiLensFamily, and can be used as a way to pass around lenses that have to be monomorphic in f.

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

Build a Getter or GetterFamily

gettingMany :: Foldable f => (a -> f c) -> MultiGetterFamily a b c dSource

Building a MultiGetter or MultiGetterFamily

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

Build a Setter or SetterFamily

Manipulating 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 MultiGetter, MultiLens or MultiLensFamily that points at monoidal values.

mapOf, modifying :: ((c -> Identity d) -> a -> Identity b) -> (c -> d) -> a -> bSource

Modify the target of a Lens, LensFamily or all the targets of a Multilens, MultiLensFamily, Setter or SetterFamily

writing :: ((c -> Identity d) -> a -> Identity b) -> d -> a -> bSource

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

(^.) :: 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)^.fstL.sndL.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.

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

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

This is an infix version of mapOf

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

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

This is an infix version of writing

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

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

 ghci> fstL ^+= 1 $ (1,2)
 (2,2)

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

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

 ghci> fstL ^-= 2 $ (1,2)
 (-1,2)

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

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

 ghci> sndL ^*= 4 $ (1,2)
 (1,8)

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

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

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

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

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

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

Manipulating State

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

Access a field of a state monad

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 

(%=) :: 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 => ((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

(+=) :: (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.

Lenses and LensFamilies

fstL :: 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.

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

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

keyL :: 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)] ^. keyL "hello"
 Just 12

intKeyL :: 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")]  ^. keyL 1
 Just "hello"
 ghci> keyL 2 ^= "goodbye" $ IntMap.fromList [(1,"hello")]
 fromList [(1,"hello"),(2,"goodbye")]

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

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

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

intMemberL :: Int -> Lens IntSet BoolSource

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

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

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

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

atL :: 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.

MultiGetters

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

MultiGetterFamily Combinators

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

 foldMapOf :: Monoid m => MultiGetterFamily 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

 foldrOf :: MultiGetterFamily a b c d -> (c -> e -> e) -> e -> a -> e

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

 foldOf :: Monoid m => MultiGetterFamily a b m d -> a -> m

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

 toListOf :: MultiGetterFamily a b c d -> a -> [c]

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

 anyOf :: MultiGetterFamily a b c d -> (c -> Bool) -> a -> Bool

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

 allOf :: MultiGetterFamily a b c d -> (c -> Bool) -> a -> Bool

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

 andOf :: MultiGetterFamily a b Bool d -> a -> Bool

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

 orOf :: MultiGetterFamily a b Bool d -> a -> Bool

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

 productOf ::  Num c => MultiGetterFamily a b c d -> a -> c

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

 sumOf ::  Num c => MultiGetterFamily a b c d -> a -> c

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

 traverseOf_ :: Applicative f => MultiGetterFamily a b c d -> (c -> f e) -> a -> f ()

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

 forOf_ :: Applicative f => MultiGetterFamily a b c d -> a -> (c -> f e) -> f ()

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

 sequenceAOf_ :: Applicative f => MultiGetterFamily a b (f ()) d -> a -> f ()

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

 mapMOf_ :: Monad m => MultiGetterFamily a b c d -> (c -> m e) -> a -> m ()

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

 forMOf_ :: Monad m => MultiGetterFamily a b c d -> a -> (c -> m e) -> m ()

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

 sequenceOf_ :: Monad m => MultiGetterFamily 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.

 asumOf :: Alternative f => MultiGetterFamily 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.

 msumOf :: MonadPlus m => MultiGetterFamily a b c d -> a -> m c

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

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

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

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

 elemOf :: Eq c => MultiGetterFamily a b c d -> c -> a -> Bool

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

 notElemOf :: Eq c => MultiGetterFamily a b c d -> c -> a -> Bool

MultiLenses

constML :: MultiLensFamily a a c dSource

This is the partial lens that never succeeds at returning any values

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

keyML :: Ord k => k -> MultiLens (Map k v) vSource

 keyML :: (Applicative f, Ord k) => k -> (v -> f v) -> Map k v -> f (Map k v)
 keyML k = keyL k . traverse

intKeyML :: Int -> MultiLens (IntMap v) vSource

 intKeyML :: Applicative f => Int -> (v -> f v) -> IntMap v -> f (IntMap v)
 intKeyML k = intKeyL k . traverse

headML :: MultiLens [a] aSource

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

tailML :: MultiLens [a] [a]Source

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

leftML :: MultiLensFamily (Either a c) (Either b c) a bSource

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

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

rightML :: MultiLensFamily (Either c a) (Either c b) a bSource

A multilens for tweaking the right-hand value in an Either:

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

Unfortunately the instance for 'Traversable (Either c)' is still missing from base.

elementML :: Traversable t => Int -> MultiLens (t a) aSource

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

MultiLens Combinators

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

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

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

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

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 Traversal f Source

Instances