explicit-constraint-lens-0.1.0.0: Fully-flexible polymorphic lenses, without any bizarre profunctors

Copyright(c) Justus Sagemüller 2017
LicenseGPL v3
Maintainer(@) sagemueller $ geo.uni-koeln.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Lens.Explicit

Contents

Description

 

Synopsis

Lenses and other optics

Getters

to :: (𝑠 -> 𝑎) -> Getter 𝑠 𝑎 Source #

type Getter 𝑠 𝑎 = Getter 𝑠 𝑠 𝑎 𝑎 Source #

Getters are basically just functions: accessors which can read a field (type 𝑎) of some data structure (type 𝑠), but not write back anything to the structure.

type AGetter 𝑠 𝑎 = AGetter 𝑠 𝑎 Source #

A getter that may also have additional capabilities, e.g. a Lens.

(^.) :: 𝑠 -> AGetter 𝑠 𝑎 -> 𝑎 infixl 8 Source #

Setters

sets :: ((𝑎 -> 𝑏) -> 𝑠 -> 𝑡) -> Setter 𝑠 𝑡 𝑎 𝑏 Source #

type Setter 𝑠 𝑡 𝑎 𝑏 = Setter 𝑠 𝑡 𝑎 𝑏 Source #

Setters are accessors that can write/manipulate a field (type 𝑎) of a data structure (type 𝑠), but not retrieve any results.

The manipulation might result in a type 𝑏 for the field different from the original 𝑎, in that case, the data structure will likewise change change its type from 𝑠 to 𝑡.

type ASetter 𝑠 𝑡 𝑎 𝑏 = ASetter 𝑠 𝑡 𝑎 𝑏 Source #

A setter that may also have additional capabilities, e.g. a Lens.

(%~) :: ASetter 𝑠 𝑡 𝑎 𝑏 -> (𝑎 -> 𝑏) -> 𝑠 -> 𝑡 infixr 4 Source #

(.~) :: ASetter 𝑠 𝑡 𝑎 𝑏 -> 𝑏 -> 𝑠 -> 𝑡 infixr 4 Source #

type Setter' 𝑠 𝑎 = Setter 𝑠 𝑠 𝑎 𝑎 Source #

Lenses

lens :: (𝑠 -> 𝑎) -> (𝑠 -> 𝑏 -> 𝑡) -> Lens 𝑠 𝑡 𝑎 𝑏 Source #

type Lens 𝑠 𝑡 𝑎 𝑏 = Lens 𝑠 𝑡 𝑎 𝑏 Source #

Lenses combine the capabilities of Getter and Setter – they have “read and write permission”, i.e. you can use them with the ^. as well as .~ and %~ operators.

This is the standard type of record-field accessor.

type ALens 𝑠 𝑡 𝑎 𝑏 = ALens 𝑠 𝑡 𝑎 𝑏 Source #

A lens that may also have additional capabilities, e.g. an Iso.

(%%~) :: Functor 𝑓 => ALens 𝑠 𝑡 𝑎 𝑏 -> (𝑎 -> 𝑓 𝑏) -> 𝑠 -> 𝑓 𝑡 infixr 4 Source #

type Lens' 𝑠 𝑎 = Lens 𝑠 𝑠 𝑎 𝑎 Source #

Prisms

prism :: (𝑏 -> 𝑡) -> (𝑠 -> Either 𝑡 𝑎) -> Prism 𝑠 𝑡 𝑎 𝑏 Source #

type Prism 𝑠 𝑡 𝑎 𝑏 = Prism 𝑠 𝑡 𝑎 𝑏 Source #

Prisms are the categorical dual of lenses: whilst a lens focuses in on a field of a record structure (i.e. of a product type), a prism distinguishes constructors of an alternative (i.e. of a sum type).

type APrism 𝑠 𝑡 𝑎 𝑏 = APrism 𝑠 𝑡 𝑎 𝑏 Source #

A prism that may also have additional capabilities, e.g. an Iso.

matching :: APrism 𝑠 𝑡 𝑎 𝑏 -> 𝑠 -> Either 𝑡 𝑎 Source #

type Prism' 𝑠 𝑎 = Prism 𝑠 𝑠 𝑎 𝑎 Source #

Reviews

unto :: (𝑏 -> 𝑡) -> Review 𝑡 𝑏 Source #

type Review 𝑡 𝑏 = Review 𝑡 𝑡 𝑏 𝑏 Source #

Reviews are basically like constructors in languages without pattern matching: prisms without read permission. Because such a constructor is just a function, and getters are functions too, you can also consider a review as a “reverse Getter”.

type AReview 𝑡 𝑏 = AReview 𝑡 𝑏 Source #

A review that may also have additional capabilities, e.g. a Prism.

re :: FromGetter c => AReview 𝑡 𝑏 -> Optic c 𝑡 𝑡 𝑏 𝑏 Source #

Isomorphisms

iso :: (𝑠 -> 𝑎) -> (𝑏 -> 𝑡) -> Iso 𝑠 𝑡 𝑎 𝑏 Source #

type Iso 𝑠 𝑡 𝑎 𝑏 = Iso 𝑠 𝑡 𝑎 𝑏 Source #

Isomorphisms are 1-1 mappings. This can be seen as a Lens which focuses on a field that contains the entire information of the data structure, or as a prism that distinguishes the only constructor available.

type AnIso 𝑠 𝑡 𝑎 𝑏 = AnIso 𝑠 𝑡 𝑎 𝑏 Source #

An isomorphism that could also have additional capabilities. (This is somewhat theoretical, since isomorphism is already the most powerful relation we describe.)

from :: AnIso 𝑠 𝑡 𝑎 𝑏 -> Iso 𝑏 𝑎 𝑡 𝑠 Source #

under :: AnIso 𝑠 𝑡 𝑎 𝑏 -> (𝑡 -> 𝑠) -> 𝑏 -> 𝑎 Source #

type Iso' 𝑠 𝑎 = Iso 𝑠 𝑠 𝑎 𝑎 Source #

Folds

folded :: Foldable 𝑓 => Fold (𝑓 𝑎) 𝑎 Source #

type Fold 𝑠 𝑎 = Fold 𝑠 𝑠 𝑎 𝑠 Source #

Folds access fields that may occur multiple times in the data structure, or not at all, such as the elements of a list. Like Getter, they don't have “write permission”.

type AFold 𝑠 𝑎 = AFold 𝑠 𝑠 𝑎 𝑠 Source #

A fold that may also have additional capabilities, e.g. a Getter or Traversal.

foldMapOf :: Monoid 𝑟 => AFold 𝑠 𝑎 -> (𝑎 -> 𝑟) -> 𝑠 -> 𝑟 Source #

Traversals

traversed :: (forall 𝑓. Applicative 𝑓 => (𝑎 -> 𝑓 𝑏) -> 𝑠 -> 𝑓 𝑡) -> Traversal 𝑠 𝑡 𝑎 𝑏 Source #

type Traversal 𝑠 𝑡 𝑎 𝑏 = Traversal 𝑠 𝑡 𝑎 𝑏 Source #

Traversals can Fold over the fields of a data structure, and additionally reconstruct the structure with modified fields.

type ATraversal 𝑠 𝑡 𝑎 𝑏 = ATraversal 𝑠 𝑡 𝑎 𝑏 Source #

A traversal that may also have additional capabilities, e.g. a Lens or Prism.

traverseOf :: Applicative 𝑓 => ATraversal 𝑠 𝑡 𝑎 𝑏 -> (𝑎 -> 𝑓 𝑏) -> 𝑠 -> 𝑓 𝑡 Source #

type Traversal' 𝑠 𝑎 = Traversal 𝑠 𝑠 𝑎 𝑎 Source #

Composition

Optics compose “OO style”, from left to right. For example, given

data Foo = Foo Int String
foostr :: Lens' Foo String
data Bar = Bar Foo Bool
barfoo :: Lens' Bar Foo

hideout :: bar
hideout = Bar (Foo 7 "I'm here!") True

you can use

   hideout ^. barfoo.foostr

to look up the "I'm here!" string.

Optics of different power can directly be composed with each other, for instance, in the example above it would have also been sufficient if

barfoo :: Getter Bar Foo

id :: Category k cat => forall (a :: k). cat a a #

the identity morphism

(.) :: Category k cat => forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c infixr 9 #

morphism composition

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

Since: 4.8.0.0