large-generics-0.2.0.0: Generic programming API for large-records and large-anon
Safe HaskellNone
LanguageHaskell2010

Data.Record.Generic.Lens.VL

Description

van Laarhoven lenses for large records. The type synonym

  type Lens' s a = forall f. Functor f => (a -> f a) -> s -> f s

Appears below, however it is not exported to avoid conflicts with other libraries defining equivalent synonyms.

Synopsis

Lenses for records

data SimpleRecordLens a b where Source #

Constructors

SimpleRecordLens :: Lens' a b -> SimpleRecordLens a b 

data HKRecordLens d (f :: Type -> Type) tbl x where Source #

Lens for higher-kinded record

See lensesForHKRecord for details.

Constructors

HKRecordLens :: Lens' (tbl f) (Interpret (d f) x) -> HKRecordLens d f tbl x 

data RegularRecordLens tbl f x where Source #

Lens into a regular record

See lensesForRegularRecord

Constructors

RegularRecordLens :: Lens' (tbl f) (f x) -> RegularRecordLens tbl f x 

lensesForSimpleRecord :: forall a. Generic a => Rep (SimpleRecordLens a) a Source #

Construct lenses for each field in the record

NOTE: This is of limited use since we cannot pattern match on the resulting Rep in any meaningful way. It is possible to go through the SOP adapter, but if we do, we incur quadratic cost again.

We can do better for higher-kinded records, and better still for regular higher-kinded records. See lensesForHKRecord and lensesForRegularRecord.

lensesForHKRecord :: forall d tbl f. (Generic (tbl f), Generic (tbl Uninterpreted), HasNormalForm (d f) (tbl f) (tbl Uninterpreted)) => Proxy d -> Rep (HKRecordLens d f tbl) (tbl Uninterpreted) Source #

Lenses for higher-kinded records

NOTE: The lenses constructed by this function are primarily intended for further processing, either by lensesForRegularRecord or using application specific logic. Details below.

Suppose we have a record tbl f which is indexed by a functor f, and we want to construct lenses from tbl f to each field in the record. Using the Transform infrastructure, we can construct a lens

tbl f ~~> Rep I (tbl f) ~~> Rep (Interpret (d f)) (tbl Uninterpreted)

Using repLenses we can construct a lens of type

Rep (Interpret (d f)) (tbl Uninterpreted) ~~> Interpret (d f) x

for every field of type x. Putting these two together gives us a lens

tbl f ~~> Interpret (d f) x

for every field in tbl Uninterpreted. We cannot simplify this, because we do not know anything about the shape of x; specifically, it might not be equal to Uninterpreted x' for some x', and hence we cannot simplify the target type of the lens. We can do better for records with regular fields; see lensesForRegularRecord.

lensesForRegularRecord :: forall d tbl f. (Generic (tbl (RegularRecordLens tbl f)), Generic (tbl Uninterpreted), Generic (tbl f), HasNormalForm (d (RegularRecordLens tbl f)) (tbl (RegularRecordLens tbl f)) (tbl Uninterpreted), HasNormalForm (d f) (tbl f) (tbl Uninterpreted), Constraints (tbl Uninterpreted) (IsRegularField Uninterpreted), StandardInterpretation d (RegularRecordLens tbl f), StandardInterpretation d f) => Proxy d -> tbl (RegularRecordLens tbl f) Source #

Lenses into higher-kinded records with regular fields

We can use lensesForHKRecord to construct a Rep of lenses into a higher-kinded record. If in addition the record is regular, we can use the record type itself to store all the lenses.

Regular records

data RegularField f x where Source #

Proof that x is a regular field

See IsRegularField

Constructors

RegularField :: RegularField f (f x) 

class IsRegularField f x where Source #

Regular record fields

For a higher-kinded record tbl f, parameterized over some functor f, we say that the fields are regular iff every field has the form f x for some x.

Methods

isRegularField :: Proxy (f x) -> RegularField f x Source #

Instances

Instances details
IsRegularField f (f x) Source # 
Instance details

Defined in Data.Record.Generic.Lens.VL

Methods

isRegularField :: Proxy (f (f x)) -> RegularField f (f x) Source #

Lenses into Rep

data RepLens f a x where Source #

Constructors

RepLens :: Lens' (Rep f a) (f x) -> RepLens f a x 

General purpose lenses

genericLens :: Generic a => Lens' a (Rep I a) Source #

normalForm1Lens :: HasNormalForm (d f) (x f) (x Uninterpreted) => Proxy d -> Lens' (Rep I (x f)) (Rep (Interpret (d f)) (x Uninterpreted)) Source #

standardInterpretationLens :: forall d f x. StandardInterpretation d f => Proxy d -> Lens' (Interpret (d f) (Uninterpreted x)) (f x) Source #