lens-sop-0.2.0.3: Computing lenses generically using generics-sop

Safe HaskellNone
LanguageHaskell2010

Generics.SOP.Lens

Contents

Description

Generalized lenses

Intended to be imported qualified

import Generics.SOP.Lens as GLens
Synopsis

Generalized lenses

data GLens r w a b Source #

GLens generalizes a monomorphic lens by allowing for different categories for the getter and modifier

Instances
(Category r, ArrowApply w) => Category (GLens r w :: Type -> Type -> Type) Source # 
Instance details

Defined in Generics.SOP.Lens

Methods

id :: GLens r w a a #

(.) :: GLens r w b c -> GLens r w a b -> GLens r w a c #

lens :: r a b -> w (w b b, a) a -> GLens r w a b Source #

get :: GLens r w a b -> r a b Source #

modify :: GLens r w a b -> w (w b b, a) a Source #

set :: Arrow w => GLens r w a b -> w (b, a) a Source #

Conversion

fromLens :: (Arrow r, ArrowApply w) => Lens (->) a b -> GLens r w a b Source #

fromIso :: (Arrow r, ArrowApply w) => Iso (->) a b -> GLens r w a b Source #

toLens :: GLens cat cat a b -> Lens cat a b Source #

Generic computation of lenses for record type

glenses :: forall r w a xs. (Generic a, Code a ~ '[xs], Arrow r, ArrowApply w) => NP (GLens r w a) xs Source #

Labels for the representation types

np :: forall r w xs. (Arrow r, ArrowApply w, SListI xs) => NP (GLens r w (NP I xs)) xs Source #

rep :: (Arrow r, ArrowApply w, Generic a) => GLens r w a (Rep a) Source #

sop :: (Arrow r, ArrowApply w) => GLens r w (SOP f '[xs]) (NP f xs) Source #

head :: (Arrow r, ArrowApply w) => GLens r w (NP f (x ': xs)) (f x) Source #

tail :: (Arrow r, ArrowApply w) => GLens r w (NP f (x ': xs)) (NP f xs) Source #

i :: (Arrow r, ArrowApply w) => GLens r w (I a) a Source #