data-lens-2.10.6: Used to be Haskell 98 Lenses

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Lens.Common

Contents

Synopsis

Documentation

newtype Lens a b Source

Constructors

Lens 

Fields

runLens :: a -> Store b a
 

Lens construction

lens :: (a -> b) -> (b -> a -> a) -> Lens a b Source

build a lens out of a getter and setter

iso :: (a -> b) -> (b -> a) -> Lens a b Source

build a lens out of an isomorphism

Functional API

getL :: Lens a b -> a -> b Source

Gets the getter function from a lens.

setL :: Lens a b -> b -> a -> a Source

Gets the setter function from a lens.

modL :: Lens a b -> (b -> b) -> a -> a Source

Gets the modifier function from a lens.

mergeL :: Lens a c -> Lens b c -> Lens (Either a b) c Source

Operator API

(^$) :: Lens a b -> a -> b infixr 0 Source

(^$!) :: Lens a b -> a -> b infixr 0 Source

(^.) :: a -> Lens a b -> b infixl 9 Source

functional getter, which acts like a field accessor

(^!) :: a -> Lens a b -> b infixl 9 Source

functional getter, which acts like a field accessor

(^=) :: Lens a b -> b -> a -> a infixr 4 Source

(^!=) :: Lens a b -> b -> a -> a infixr 4 Source

(^%=) :: Lens a b -> (b -> b) -> a -> a infixr 4 Source

functional modify

(^!%=) :: Lens a b -> (b -> b) -> a -> a infixr 4 Source

functional modify

(^%%=) :: Functor f => Lens a b -> (b -> f b) -> a -> f a infixr 4 Source

functorial modify

Pseudo-imperatives

(^+=) :: Num b => Lens a b -> b -> a -> a infixr 4 Source

(^!+=) :: Num b => Lens a b -> b -> a -> a infixr 4 Source

(^-=) :: Num b => Lens a b -> b -> a -> a infixr 4 Source

(^!-=) :: Num b => Lens a b -> b -> a -> a infixr 4 Source

(^*=) :: Num b => Lens a b -> b -> a -> a infixr 4 Source

(^!*=) :: Num b => Lens a b -> b -> a -> a infixr 4 Source

(^/=) :: Fractional b => Lens a b -> b -> a -> a infixr 4 Source

(^!/=) :: Fractional b => Lens a b -> b -> a -> a infixr 4 Source

Stock lenses

fstLens :: Lens (a, b) a Source

sndLens :: Lens (a, b) b Source

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

setLens :: Ord k => k -> Lens (Set k) Bool Source