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

Safe HaskellNone
LanguageHaskell2010

Generics.SOP.Lens.Computed

Contents

Synopsis

Abstract lenses

data AbstractLens r w c a Source #

An abstract lens qualifies existentially over the target type of the lens

Sadly, abstract lenses do not form a category, so we provide special identity and composition functions.

Constructors

c x => AbstractLens (GLens r w a x) 

abstractId :: (ArrowApply r, ArrowApply w, c a) => AbstractLens r w c a Source #

Identity abstract lens

afterGLens Source #

Arguments

:: (ArrowApply r, ArrowApply w) 
=> AbstractLens r w c a
a -> x
-> GLens r w b a
b -> a
-> AbstractLens r w c b
b -> x

Compose with a pointwise lens on the right

Getters and setters

get :: Category r => AbstractLens r w c a -> (forall x. c x => r a x -> b) -> b Source #

Getter for computed lenses

get l == runIdentity . getM l . Identity

set :: Arrow w => AbstractLens r w c a -> (forall x. c x => x) -> w a a Source #

Setter for computed lenses

set l == runIdentity . setM l . Identity

modify :: Arrow w => AbstractLens r w c a -> (forall x. c x => w x x) -> w a a Source #

Modifier for computed lenses

getM :: (Monad m, Category r) => AbstractLens r w c a -> (forall x. c x => r a x -> m b) -> m b Source #

Getter with possibility for "compile time" failure

setM :: (Monad m, Arrow w) => AbstractLens r w c a -> (forall x. c x => m x) -> m (w a a) Source #

Setter with possibility for "compile time" failure

modifyM :: (Monad m, Arrow w) => AbstractLens r w c a -> (forall x. c x => m (w x x)) -> m (w a a) Source #

Modifier with possibility for "compile time" failure

Computing lenses

type Path = [String] Source #

A path is a series of field names. For instance, given

data T1 = T1 { a :: Int, b :: Int } deriving Generic
data T2 = T2 { c :: T1,  d :: Int } deriving Generic

valid paths on T2 are

[]
["c"]
["d"]
["c", "a"]
["c", "b"]

class CLens r w c a Source #

Compute a lens for a given type and path

The Either is used to indicate "compile time" failure of the computation of the lens (for instance, when this path is invalid for this data type).

Some lenses may of course be themselves effectful, depending on the category. However, the lenses returned by the generic computation are pure and total (as is evident from the type of glens).

lens :: CLens r w c a => LensOptions -> Path -> Either String (AbstractLens r w c a) Source #

Manually constructing lenses

emptyPathOnly :: (ArrowApply r, ArrowApply w, c a) => LensOptions -> Path -> Either String (AbstractLens r w c a) Source #

A lens for abstract types (supports empty paths only)

Useful for defining CLens instances for types such as Int, Bool, Text, etc.

instance CLens c Int where lens = emptyPathOnly

Configuration

data LensOptions Source #

Constructors

LensOptions 

Fields

defaultLensOptions :: LensOptions Source #

Default match just compares field names