lens-0.2: 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

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

type Getter a b = forall x y z. (b -> Const z x) -> a -> Const z ySource

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

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

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

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

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 :: Functor f => (a -> c) -> (d -> a -> b) -> (c -> f d) -> a -> f bSource

Build a lens from a getter and a setter

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

Built a lens from an isomorphism or an isomorphism family

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 -> b) -> Getter a bSource

Build a getter

gettingMany :: Foldable f => (a -> f b) -> MultiGetter a bSource

Building a multigetter

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

Build a setter

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 => MultiGetter (f a) aSource

MultiGetter combinators

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

 foldMapOf :: Monoid m => MultiGetter a b -> (b -> m) -> a -> m

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

 foldrOf :: MultiGetter a b -> (b -> c -> c) -> c -> a -> c

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

 foldOf :: Monoid m => MultiGetter a m -> a -> m

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

 toListOf :: MultiGetter a b -> a -> [b]

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

 anyOf :: MultiGetter a b -> (b -> Bool) -> a -> Bool

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

 allOf :: MultiGetter a b -> (b -> Bool) -> a -> Bool

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

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

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

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

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

 traverseOf_ :: Applicative f => MultiGetter a b -> (b -> f c) -> a -> f ()

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

 forOf_ :: Applicative f => MultiGetter a b -> a -> (b -> f c) -> f ()

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

 sequenceAOf_ :: Applicative f => MultiGetter a (f ()) -> 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 => MultiGetter a b -> (b -> m c) -> 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 => MultiGetter a b -> a -> (b -> m c) -> m ()

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

 sequenceOf_ :: Monad m => MultiGetter a (m b) -> 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.

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.

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

concatMapOf :: MultiGetter a c -> (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

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

MultiLenses

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

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

keyML :: (Applicative f, Ord k) => k -> (v -> f v) -> Map k v -> f (Map k v)Source

intKeyML :: Applicative f => Int -> (v -> f v) -> IntMap v -> f (IntMap v)Source

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

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

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

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

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