lens-family-core-0.0.1: Haskell 98 Lens Families

Safe HaskellSafe-Infered

Lens.Family

Contents

Description

This is the main module for end-users of lens-families. If you are not building your own lenses, but just using top-level defined lenses made by others, this is the only module you need. It provides ^. for accessing fields and ^= and ^%= for setting and modifying fields. Lenses are composed with . from the Prelude and id is the identity lens.

Warning: Lenses are composed in the opposite order than most lens packages. Lenses in this library enjoy the following identities.

  • x ^. l1 . l2 === x ^. l1 ^. l2
  • l1 . l2 ^%= f === l1 ^%= l2 ^%= f

The identity lens behaves as follows.

  • x ^. id === x
  • id ^%= f === f

Lenses are implemented in van Laarhoven style. Lenses have type Functor f => (b -> f b) -> a -> f a and lens families have type Functor f => (b x -> f (b x')) -> a x -> f (a x').

Remember that lenses and lens families can be used directly for functorial updates. For example, sndL id gives you strength.

 sndL id :: Functor f => (a, f b) -> f (a, b)

Here is an example of code that uses the Maybe functor to preserves sharing during update when possible.

 -- | 'sharedUpdate' returns the *identical* object if the update doesn't change anything.
 -- This is useful for preserving sharing.
 sharedUpdate :: Eq b => Lens Maybe a b -> (b -> b) -> a -> a
 sharedUpdate lens f a = fromMaybe a (lens f' a)
  where
   f' b | fb == b  = Nothing
        | otherwise = Just fb
    where
     fb = f b

For stock lenses, see Lens.Family.Stock.

To build your own lenses, see Lens.Family.Unchecked.

References:

Synopsis

Documentation

getting :: (a -> b) -> GetterFamily a a' b b'Source

getting promotes a projection function to a read-only lens. To demote a lens to a projection function, use the section (^. l).

>>> (3 :+ 4, "example") ^. fstL . getting abs
5.0 :+ 0.0

setting :: ((b -> b') -> a -> a') -> SetterFamily a a' b b'Source

setting promotes a "semantic editor combinator" to a modify-only lens. To demote a lens to a semantic edit combinator, use the section (l ^%=).

>>> setting map . fstL ^%= length $ [("The",0),("quick",1),("brown",1),("fox",2)]
[(3,0),(5,1),(5,1),(3,2)]

(^.) :: a -> GetterFamily a a' b b' -> bSource

Access a field.

(^%=) :: SetterFamily a a' b b' -> (b -> b') -> a -> a'Source

Modify a field.

(^=) :: SetterFamily a a' b b' -> b' -> a -> a'Source

Set a field.

Pseudo-imperatives

(^+=), (^*=), (^-=) :: Num b => Setter a b -> b -> a -> aSource

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

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

Types

type GetterFamily a a' b b' = LensFamily (Getting b) a a' b b'Source

type Getter a b = GetterFamily a a b bSource

type SetterFamily a a' b b' = LensFamily Setting a a' b b'Source

type Setter a b = SetterFamily a a b bSource