linear-base-0.1.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Optics.Linear.Lens

Description

This module provides linear lenses.

A Lens s t a b is equivalent to a (s #-> (a,b #-> t). It is a way to cut up an instance of a product type s into an a and a way to take a b to fill the place of the a in s which yields a t. When a=b and s=t, this type is much more intuitive: (s #-> (a,a #-> s)). This is a traversal on exactly one a in a s.

Example

{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}

import Control.Optics.Linear.Internal
import Prelude.Linear

import Control.Optics.Linear.Internal
import Prelude.Linear
-- We can use a lens to, for instance, linearly modify a sub-piece in
-- a nested record
modPersonZip :: Person %1-> Person
modPersonZip = over (personLocL .> locZipL)  (x -> x + 1)

-- A person has a name and location
data Person = Person String Location

-- A location is a zip code and address
data Location = Location Int String

personLocL :: Lens' Person Location
personLocL = lens ((Person s l) -> (l, l' -> Person s l'))

locZipL :: Lens' Location Int
locZipL = lens ((Location i s) -> (i, i' -> Location i' s))
Synopsis

Types

type Lens s t a b = Optic (Strong (,) ()) s t a b Source #

type Lens' s a = Lens s s a a Source #

Composing lens

(.>) :: Optic_ arr s t a b -> Optic_ arr a b x y -> Optic_ arr s t x y Source #

Common optics

_1 :: Lens (a, c) (b, c) a b Source #

_2 :: Lens (c, a) (c, b) a b Source #

Using optics

get :: Optic_ (Kleisli (Const a)) s t a b -> s -> a Source #

set :: Optic_ (->) s t a b -> b -> s -> t Source #

gets :: Optic_ (Kleisli (Const r)) s t a b -> (a -> r) -> s -> r Source #

setSwap :: Optic_ (Kleisli (Compose (LinearArrow b) ((,) a))) s t a b -> s %1 -> b %1 -> (a, t) Source #

over :: Optic_ LinearArrow s t a b -> (a %1 -> b) -> s %1 -> t Source #

overU :: Optic_ (->) s t a b -> (a -> b) -> s -> t Source #

reifyLens :: Optic_ (Kleisli (Compose ((,) a) (FUN 'One b))) s t a b -> s %1 -> (a, b %1 -> t) Source #

withLens :: Optic_ (Kleisli (Compose ((,) a) (FUN 'One b))) s t a b -> (forall c. (s %1 -> (c, a)) -> ((c, b) %1 -> t) -> r) -> r Source #

Constructing optics

lens :: (s %1 -> (a, b %1 -> t)) -> Lens s t a b Source #