lens-0.1: Lenses and Lens Families

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Lens

Contents

Description

A self-contained lens library with lenses that are compatible with other van Laarhoven lens libraries.

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 (.).

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

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

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

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

Reading from lenses

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

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

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

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

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

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

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

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

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

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

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

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

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

Manipulating state

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

class Focus st whereSource

Methods

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

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

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

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

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

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

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

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

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

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

Common lenses

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

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

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

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

Getters

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

getting :: (a -> c) -> (c -> Const r d) -> a -> Const r bSource

Setters

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

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

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

Implementation details

data IndexedStore c d a Source

Constructors

IndexedStore (d -> a) c 

Instances

newtype Focusing m c a Source

Constructors

Focusing 

Fields

unfocusing :: m (c, a)
 

Instances

Monad m => Functor (Focusing m c)