yall-0.1: Lenses with a southern twang

Safe HaskellSafe-Infered

Data.Yall.Lens

Contents

Synopsis

Documentation

The Lenses here are parameterized over two Monads (by convention m and w), so that the "extract" and "rebuild" phases of a lens set operation each happen within their own environment.

Concretely, a lens like (:->) with both environments set to the trivial Identity Monad, gives us the usual pure lens, whereas something like (:~>), where the m environment is Maybe gives one possibility for a partial lens. These would be suitable for multi-constructor data types.

One might also like to use a lens as an interface to a type, capable of performing validation (beyond the capabilities of the typechecker). In that case the w environment becomes useful, and you might have :: Lens Maybe Identity PhoneNumber [Int].

See "Monadic API" below for a concrete example.

newtype Lens w m a b Source

Constructors

Lens 

Fields

runLens :: a -> m (b -> w a, b)
 

Instances

Monad m => Functor m (Lens m m) (Lens Identity Identity) 
(Monad w, Monad m) => PFunctor (,) (Lens w m) (Lens w m) 
(Monad w, Monad m) => QFunctor (,) (Lens w m) (Lens w m) 
(Monad w, Monad m) => Bifunctor (,) (Lens w m) (Lens w m) (Lens w m) 
(Monad w, Monad m) => Category (Lens w m) 
(Monad w, Monad m) => HasTerminalObject (Lens w m) 
(Monad w, Monad m) => Braided (Lens w m) (,) 
(Monad w, Monad m) => Symmetric (Lens w m) (,) 
(Monad w, Monad m) => Monoidal (Lens w m) (,) 
(Monad w, Monad m) => Comonoidal (Lens w m) (,) 
(Monad w, Monad m) => Associative (Lens w m) (,) 
(Monad w, Monad m) => Disassociative (Lens w m) (,) 

Simple API

Pure lenses

type :-> = LensM IdentitySource

a simple lens, suitable for single-constructor types

lens :: (a -> b) -> (a -> b -> a) -> a :-> bSource

Create a pure Lens from a getter and setter

 lens g = lensM (fmap return g) . fmap (fmap return)

get :: Lens w Identity a b -> a -> bSource

Run the getter function of a pure lens

 get l = runIdentity . getM l

set :: (a :-> b) -> b -> a -> aSource

Run the getter function of a pure lens

 set l b = runIdentity . setM l b

modify :: (a :-> b) -> (b -> b) -> a -> aSource

Partial lenses

type :~> = LensM MaybeSource

a lens that can fail in the Maybe monad on the outer type. Suitable for a normal lens on a multi-constructor type. The more general setM, getM, etc. can be used with this type.

Monadic API

In addition to defining lenses that can fail and perform validation, we have the ability to construct more abstract and expressive Lenses. Here is an example of a lens on the "N-th" element of a list, that returns its results in the [] monad:

 nth :: LensM [] [a] a
 nth = Lens $ foldr build []
     where build n l = (return . (: map snd l), n) : map (prepend n) l
           prepend = first . fmap . liftM . (:)

We can compose this with other lenses like the lens on the snd of a tuple, just as we would like:

>>> setM (sndL . nth) 0 [('a',1),('b',2),('c',3)]
[[('a',0),('b',2),('c',3)],[('a',1),('b',0),('c',3)],[('a',1),('b',2),('c',0)]]

Lenses with monadic getters

type LensM = Lens IdentitySource

A lens in which the setter returns its result in the trivial identity monad. This is appropriate e.g. for traditional partial lenses, where there is a potential that the lens could fail only on the outer constructor.

lensM :: Monad m => (a -> m b) -> (a -> m (b -> a)) -> LensM m a bSource

Create a monadic lens from a getter and setter

getM :: Monad m => Lens w m a b -> a -> m bSource

get, returning the result in a Monadic environment. This is appropriate e.g. for traditional partial lenses on multi-constructor types. See also setM

setM :: Monad m => LensM m a b -> b -> a -> m aSource

set, returning the result in the getter's Monadic environment, running the setter's trivial Identity monad.

modifyM :: Monad m => LensM m a b -> (b -> b) -> a -> m aSource

modify the inner value within the getter's Monadic environment

Monadic variants

The setter continuation is embedded in the getter's Monadic environment, so we offer several ways of combining different types of getter environments(m) and setter environments (w), for Lenses with complex effects.

lensMW :: Monad m => (a -> m b) -> (a -> m (b -> w a)) -> Lens w m a bSource

Create a monadic Lens from a setter and getter.

 lensMW g s = Lens $ \a-> liftM2 (,) (s a) (g a)

setW :: Monad w => Lens w Identity a b -> b -> a -> w aSource

set, with Monadic setter & pure getter

modifyW :: Monad w => Lens w Identity a b -> (b -> b) -> a -> w aSource

setLiftM :: (Monad (t m), MonadTrans t, Monad m) => Lens (t m) m a b -> b -> a -> t m aSource

set, lifting the outer (getter's) Monadic environment to the type of the setter monad transformer.

setLiftW :: (MonadTrans t, Monad (t w), Monad w) => Lens w (t w) a b -> b -> a -> t w aSource

set, like setLiftM but we lift the inner setter's environment to the outer getter monad transformer.

setJoin :: Monad m => Lens m m a b -> b -> a -> m aSource

set, combining the effects of the identical setter and getter Monads with join.

Monoid setters

setEmpty :: Monoid a => (a :-> b) -> b -> aSource

Set an inner value on an initially mempty value.

 setZero l b = set l b mzero

setEmptyM :: (Monoid a, Monad m) => LensM m a b -> b -> m aSource

 setZeroM l b = setM l b mzero

setEmptyW :: (Monoid a, Monad w) => Lens w Identity a b -> b -> w aSource

 setEmptyW l b = setW l b mempty

Composing Lenses

In addition to the usual Category instance, we define instances for Lens for a number of category-level abstractions from the categories package. Here are the various combinators and pre-defined lenses from these classes, with types shown for a simplified Lens type.

 import Control.Categorical.Bifunctor
 first :: Lens a b -> Lens (a,x) (b,x)
 second :: Lens a b -> Lens (x,a) (x,b)
 bimap :: Lens a b -> Lens x y -> Lens (a,x) (b,y)
 import Control.Categorical.Object
 terminate :: Lens a ()
 import Control.Category.Associative
 associate :: Lens ((a,b),c) (a,(b,c))
 disassociate :: Lens (a,(b,c)) ((a,b),c)
 import Control.Category.Braided
 braid :: Lens (a,b) (b,a)
 import Control.Category.Monoidal
 idl :: Lens ((), a) a
 idr :: Lens (a,()) a
 coidl :: Lens a ((),a)
 coidr :: Lens a (a,())
 import qualified Control.Categorical.Functor as C
 C.fmap :: (Monad m)=> Lens m m a b -> (m a :-> m b)

In addition the following combinators and pre-defined lenses are provided.

fstL :: (Monad m, Monad w) => Lens w m (a, b) aSource

sndL :: (Monad m, Monad w) => Lens w m (a, b) bSource

eitherL :: (Monad m, Monad w) => Lens w m (Either a a) aSource

codiag from Cartesian

 eitherL = id ||| id

(|||) :: (Monad m, Monad w) => Lens w m a c -> Lens w m b c -> Lens w m (Either a b) cSource

factorL :: (Monad m, Monad w) => Lens w m (Either (a, b) (a, c)) (a, Either b c)Source

distributeL :: (Monad m, Monad w) => Lens w m (a, Either b c) (Either (a, b) (a, c))Source

isoL :: (Monad m, Monad w) => Iso m w a b -> Lens m w a bSource

Convert an isomorphism to a Lens

Convenience operators

The little "^" hats are actually superscript "L"s (for Lens) that have fallen over.

(^$) :: Lens w Identity a b -> a -> bSource

 (^$) = get

(^>>=) :: Monad m => m a -> Lens w m a b -> m bSource

 ma ^>>= l = ma >>= getM l