yall-0.2.1: Lenses with a southern twang

Safe HaskellNone

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 m => Lenses (Lens Identity) 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) => Associative (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) -> a -> b -> aSource

Run the getter function of a pure lens

 set l b = runIdentity . setM l a

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)]]

class Monad m => Lenses l m whereSource

A class for our basic (monadic) lens operations. Minimal complete definition is getM and setM

Methods

getM :: l m a b -> a -> m bSource

setM :: l m a b -> a -> b -> m aSource

modifyM :: l m a b -> (b -> b) -> a -> m aSource

Instances

Monad w => Lenses LensW w 
Monad m => Lenses LensJoin m 
Monad m => Lenses (Lens Identity) m 
(MonadTrans t, Monad (t w), Monad w) => Lenses (LensLift w) (t w) 

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 on sum types, 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

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.

Newtype wrappers around Lens let us use the same Lenses interface for getting and setting for these various monad-combining schemes.

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)

newtype LensLift w m a b Source

lenses in which set/get should lift the inner monad w to m

Constructors

LLift (Lens w m a b) 

Instances

(MonadTrans t, Monad (t w), Monad w) => Lenses (LensLift w) (t w) 

newtype LensJoin m a b Source

lenses in which m == w and we would like to join the two in get/set

Constructors

LJoin (Lens m m a b) 

Instances

newtype LensW w a b Source

lenses in which only the setter w is monadic

Constructors

LW (Lens w Identity a b) 

Instances

Monad w => Lenses LensW w 

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

Lenses from Isomorphisms

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

Convert an isomorphism i to a Lens. When apply i . unapply i = unapply i . apply i = id, the resulting lens will be well-behaved.

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

Convert to a Lens an isomorphism between a value a and a tuple of a value b with some "residual" value r.

Convenience operators

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

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

 (^$) = get

(^>>=) :: Lenses l m => m a -> l m a b -> m bSource

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