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

Safe HaskellSafe-Infered

Lens.Family.Unchecked

Contents

Description

Caution: Improper use of this module can lead to unexpected behaviour if the preconditions of the functions are not met.

A lens family is created by separating a substructure from the rest of its structure by a functor. How to create a lens family is best illustrated by the common example of a field of a record:

 data MyRecord a = MyRecord { _myA :: a, _myB :: Int }

 -- The use of type variables a and a' allow for polymorphic updates.
 myA :: Functor f => LensFamily f (MyRecord a) (MyRecord a') a a'
 myA f (MyRecord a b) = (\a' -> MyRecord a' b) `fmap` (f a)

 -- The field _myB is monomorphic, so we can use a plain Lens type.
 -- However, the structure of the function is exactly the same as for LensFamily.
 myB :: Functor f => Lens f (MyRecord a) Int
 myB f (MyRecord a b) = (\b' -> MyRecord a b') `fmap` (f b)

By following this template you can safely build your own lenses. To use this template, you do not need anything from this module other than the type synonyms LensFamily and Lens, and even they are optional. See the lens-family-th package to generate this code using Template Haskell.

You can build lenses for more than just fields of records. Any value lens :: Functor f => LensFamily f a a' b b' is well-defined when it satisfies the two van Laarhoven lens laws:

  • lens Identity === Identity
  •  lens (composeCoalgebroid f g) === composeCoalgebroid (lens f) (lens g)
      where
       composeCoalgebroid :: (Functor f, Functor g) => (b -> f c) -> (a -> g b) -> a -> (Compose g f) c
       composeCoalgebroid f g a = Compose $ f `fmap` g a === id
    

The functions mkLens and mkIsoLens can also be used to construct lenses. The resulting lenses will be well-defined so long as their preconditions are satisfied.

Synopsis

Documentation

mkLensSource

Arguments

:: Functor f 
=> (a -> b)

getter

-> (a -> b' -> a')

setter

-> LensFamily f a a' b b' 

Build a lens from a getter and setter families.

Caution: In order for the generated lens family to be well-defined, you must ensure that the three lens laws hold:

  • getter (setter a b) === b
  • setter a (getter a) === a
  • setter (setter a b1) b2) === setter a b2

mkIsoLensSource

Arguments

:: Functor f 
=> (a -> b)

yin

-> (b' -> a')

yang

-> LensFamily f a a' b b' 

Build a lens from isomorphism families.

Caution: In order for the generated lens family to be well-defined, you must ensure that the two isomorphism laws hold:

  • yin . yang === id
  • yang . yin === id

Types

type LensFamily f a a' b b' = (b -> f b') -> a -> f a'Source

type Lens f a b = LensFamily f a a b bSource