prolens-0.0.0.1: Profunctor-based lightweight implementation of optics
Copyright(c) 2020-2021 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Prolens

Description

The prolens package is a Haskell library with a minimal and lightweight implementation of optics based on Profunctors. Optic is a high-level concept for values that provide composable access to different parts of structures.

Prolens implements the following optics:

  • Lens — composable getters and setters
  • Prism — composable constructors and deconstructors
  • Traversal — composable data structures visitors

Usage

To use lenses or prisms in your project, you need to add prolens package as the dependency in the build-depends field of your .cabal file. E.g.:

build-depends: prolens ^>= 0.0.0.0

You should add the import of this module in the place of lenses usage:

import Prolens

Creating your own optics

We show in each section of this module how to create values of each kind of optics.

⚠️ The general crucial rule for achieving maximum performance: always add {-# INLINE ... #-} pragmas to your optics.

Typeclasses table

The below table shows required constraints for each Optic:

OpticConstraints
LensStrong p
PrismChoice p
Traversal(Choice p, Monoidal p)

Usage table: get, set, modify

Here is a go-to table on how to use getter, setters and modifiers with different Optics.

getget operatorsetset operatormodifymodify operator
Lensview l xx ^. lset l new xx & l .~ newover l f xx & l %~ f
Prismpreview _L x-set _L new x-over _L f x-
Traversalview l x-set l new x-over l f x-

Since: 0.0.0.0

Synopsis

Profunctor typeclass

class (forall a. Functor (p a)) => Profunctor p where Source #

The type p is called Profunctor and it means, that a value of type p in out takes a value of type in as an argument (input) and outputs a value of type out. Profunctor allows mapping of inputs and outputs.

          +----> Result input
          |
          |                                +--> Original profunctor
          |      +-> Original input        |
          +      +                         +
dimap :: (in2 -> in1) -> (out1 -> out2) -> p in1 out1 -> p in2 out2
                          +       +
                          |       +-> Result output
                          |
                          +-> Original output

Speaking in terms of other abstractions, Profunctor is Contravariant in the first type argument (type variable in) and Functor in the second type argument (type variable out).

Moreover, p in must have Functor instance first to implement the Profunctor instance. This required using QuantifiedConstraints.

                         Contravariant <---+
                                           |
                                         +-+-+
                                         +   +
(forall a . Functor (p a)) => Profunctor p a b
          +                              + +
          |                              | |
          +--> Quantified constraint     +++
                                          |
                              Functor  <--+

Instances of Profunctor should satisfy the following laws:

Since: 0.0.0.0

Methods

dimap Source #

Arguments

:: (in2 -> in1)

Map input

-> (out1 -> out2)

Map output

-> p in1 out1

Take in1 as input and return out1

-> p in2 out2

Take in2 as input and return out2

Instances

Instances details
Profunctor (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

dimap :: (in2 -> in1) -> (out1 -> out2) -> Forget r in1 out1 -> Forget r in2 out2 Source #

Functor m => Profunctor (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

dimap :: (in2 -> in1) -> (out1 -> out2) -> Fun m in1 out1 -> Fun m in2 out2 Source #

Profunctor ((->) :: Type -> Type -> Type) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

dimap :: (in2 -> in1) -> (out1 -> out2) -> (in1 -> out1) -> in2 -> out2 Source #

Optics

type Optic p source target a b = p a b -> p source target Source #

Optic takes a connection from a to b (represented as a value of type p a b) and returns a connection from source to target (represented as a value of type p source target).

           +---> Profunctor
           |
           | +----> Final input
           | |
           | |      +-> Final output
           | |      |
           + +      +
type Optic p source target a b
                           + +
                           | |
            Given input <--+ |
                             |
        Given output <-------+

Since: 0.0.0.0

Lenses

Example

To understand better how to use this library lets look at some simple example. Let's say we have the user and address data types in our system:

>>> :{
data Address = Address
    { addressCountry :: String
    , addressCity    :: String
    , addressIndex   :: String
    } deriving (Show)
:}
>>> :{
data User = User
    { userName    :: String
    , userAge     :: Int
    , userAddress :: Address
    } deriving (Show)
:}

We can easily get fields of the User and Address types, but setting values is inconvenient (especially for nested records). To solve this problem, we can use lenses — composable getters and setters. Lens is a value, so we need to define lenses for fields of our data types first.

To create the lens for the userName field we can use lens function and manually writing getter and setter function:

>>> :{
nameL :: Lens' User String
nameL = lens getter setter
  where
    getter :: User -> String
    getter = userName
    setter :: User -> String -> User
    setter user newName = user {userName = newName}
:}

In this manner, we can create other lenses for our User data type. Usually, lenses are one-liners, and we can define them easily using lambda-functions.

>>> :{
ageL :: Lens' User Int
ageL = lens userAge (\u new -> u {userAge = new})
:}
>>> :{
addressL :: Lens' User Address
addressL = lens userAddress (\u new -> u {userAddress = new})
:}

We want to have lenses for accessing Adress fields inside User, so we want to have the following values:

countryL :: Lens' User String
cityL    :: Lens' User String
indexL   :: Lens' User String

Note: for lenses as countryL, cityL etc., we are using composition of the lenses for the userAddress field. If we have

>>> :{
addressCityL :: Lens' Address String
addressCityL = lens addressCity (\a new -> a {addressCity = new})
:}

then

>>> cityL = addressL . addressCityL

Let's say we have some sample user

>>> :{
address = Address
    { addressCountry = "UK"
    , addressCity    = "London"
    , addressIndex   = "XXX"
    }
user :: User
user = User
    { userName = "John"
    , userAge  = 42
    , userAddress = address
    }
:}

To view the fields of the User data type we can use view or ^.

>>> view ageL user
42
>>> user ^. cityL
"London"

If we want to change any of the user's data, we should use set or .~

>>> set nameL "Johnny" user
User {userName = "Johnny", userAge = 42, userAddress = Address {addressCountry = "UK", addressCity = "London", addressIndex = "XXX"}}
>>> user & cityL .~ "Bristol"
User {userName = "John", userAge = 42, userAddress = Address {addressCountry = "UK", addressCity = "Bristol", addressIndex = "XXX"}}

over or %~ operator could be useful when, for example, you want to increase the age by one on the user's birthday:

>>> over ageL succ user
User {userName = "John", userAge = 43, userAddress = Address {addressCountry = "UK", addressCity = "London", addressIndex = "XXX"}}
>>> user & ageL %~ succ
User {userName = "John", userAge = 43, userAddress = Address {addressCountry = "UK", addressCity = "London", addressIndex = "XXX"}}

Lenses types

type Lens source target a b = forall p. Strong p => Optic p source target a b Source #

Lens represents composable getters and setters.

Lens is an Optic p with the Strong constraint on the p type variable.

          +---> Current object
          |
          |      +-> Final object
          |      |
          +      +
type Lens source target a b
                        + +
                        | |
       Current field <--+ |
                          |
      Final field <-------+

Since: 0.0.0.0

type Lens' source a = Lens source source a a Source #

The monomorphic lenses which don't change the type of the container (or of the value inside). It has a Strong constraint, and it can be used whenever a getter or a setter is needed.

  • a is the type of the value inside of structure
  • source is the type of the whole structure

For most use-cases it's enought to use this Lens' instead of more general Lens.

Since: 0.0.0.0

Strong typeclass

class Profunctor p => Strong p where Source #

Strong is a Profunctor that can be lifted to take a pair as an input and return a pair.

The second element of a pair (variable of type c) can be of any type, and you can decide what type it should be. This is convenient for implementing various functions. E.g. lens uses this fact.

Instances of Strong should satisfy the following laws:

Since: 0.0.0.0

Methods

first :: p a b -> p (a, c) (b, c) Source #

second :: p a b -> p (c, a) (c, b) Source #

Instances

Instances details
Strong (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

first :: Forget r a b -> Forget r (a, c) (b, c) Source #

second :: Forget r a b -> Forget r (c, a) (c, b) Source #

Functor m => Strong (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

first :: Fun m a b -> Fun m (a, c) (b, c) Source #

second :: Fun m a b -> Fun m (c, a) (c, b) Source #

Strong ((->) :: Type -> Type -> Type) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

first :: (a -> b) -> (a, c) -> (b, c) Source #

second :: (a -> b) -> (c, a) -> (c, b) Source #

Lenses functions

set Source #

Arguments

:: p ~ (->) 
=> Optic p source target a b

Optic that can be lens

-> b

Value to set

-> source

Object where we want to set value

-> target

Resulting object with b set

Sets the given value to the structure using a setter.

Since: 0.0.0.0

over Source #

Arguments

:: p ~ (->) 
=> Optic p source target a b

Optic that can be lens

-> (a -> b)

Field modification function

-> source

Object where we want to set value

-> target

Resulting object with the modified field

Applies the given function to the target.

Since: 0.0.0.0

view Source #

Arguments

:: p ~ Fun (Const a) 
=> Optic p source target a b

Optic that can be lens

-> source

Object from which we want to get value

-> a

Field of source

Gets a value out of a structure using a getter.

Since: 0.0.0.0

lens Source #

Arguments

:: (source -> a)

Getter

-> (source -> b -> target)

Setter

-> Lens source target a b 

Creates Lens from the getter and setter.

Since: 0.0.0.0

Lenses operators

(^.) :: source -> Lens' source a -> a infixl 8 Source #

The operator form of view with the arguments flipped.

Since: 0.0.0.0

(.~) :: Lens' source a -> a -> source -> source infixr 4 Source #

The operator form of set.

Since: 0.0.0.0

(%~) :: Lens' source a -> (a -> a) -> source -> source infixr 4 Source #

The operator form of over.

Since: 0.0.0.0

Standard lenses

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

Lens' for a tuple on the first argument.

>>> view fstL (42, "str")
42

Since: 0.0.0.0

sndL :: Lens (x, a) (x, b) a b Source #

Lens' for a tuple on the second argument.

>>> view sndL (42, "Hello")
"Hello"

Since: 0.0.0.0

Prisms

Prisms work with sum types.

Example

Let's say we have the user data type in our system:

>>> :{
data Address = Address
    { addressCountry :: String
    , addressCity    :: String
    } deriving (Show)
:}
>>> :{
data Payload
    = NamePayload String
    | IdPayload Int
    | AddressPayload Address
    deriving (Show)
:}

To create the prism for each constructor we can use prism' function and manually writing getter and setter function:

NOTE: The naming convention for prisms is the following:

_ConstructorName
>>> :{
_NamePayload :: Prism' Payload String
_NamePayload = prism' construct match
  where
    match :: Payload -> Maybe String
    match p = case p of
        NamePayload name -> Just name
        _otherPayload -> Nothing
    construct :: String -> Payload
    construct = NamePayload
:}

In this manner, we can create other prisms for our Payload data type.

>>> :{
_IdPayload :: Prism' Payload Int
_IdPayload = prism' IdPayload $ \p -> case p of
    IdPayload i -> Just i
    _otherPayload -> Nothing
:}
>>> :{
_AddressPayload :: Prism' Payload Address
_AddressPayload = prism' AddressPayload $ \p -> case p of
    AddressPayload a -> Just a
    _otherPayload -> Nothing
:}

Let's say we have some sample payload

>>> :{
payloadName :: Payload
payloadName = NamePayload "Some name"
:}

To view the fields of the Payload data type we can use preview

>>> preview _NamePayload payloadName
Just "Some name"
>>> preview _IdPayload payloadName
Nothing

If we want to change any of the data, we should use set or .~ (just like in lenses)

>>> set _NamePayload "Johnny" payloadName
NamePayload "Johnny"
>>> set _IdPayload 3 payloadName
NamePayload "Some name"

Note, that you can easily compose lenses and prisms together:

>>> :{
address = Address
    { addressCountry = "UK"
    , addressCity    = "London"
    }
:}
>>> :{
addressCityL :: Lens' Address String
addressCityL = lens addressCity (\a new -> a {addressCity = new})
:}
>>> :{
payloadAddress :: Payload
payloadAddress = AddressPayload address
:}
>>> set _AddressPayload (address & addressCityL .~ "Bristol") payloadAddress
AddressPayload (Address {addressCountry = "UK", addressCity = "Bristol"})

Prism types

type Prism source target a b = forall p. Choice p => Optic p source target a b Source #

Prism represents composable constructors and deconstructors.

Prism is an Optic p with Choice constraint on the p type variable.

                   +---> Current object
                   |
                   |      +-> Final object
                   |      |
                   +      +
        type Prism source target a b
                                 + +
                                 | |
 Field in current constructor <--+ |
                                   |
Field in final constructor <-------+

Since: 0.0.0.0

type Prism' source a = Prism source source a a Source #

The monomorphic prisms which don't change the type of the container (or of the value inside).

  • a is the value inside the particular constructor
  • source is some sum type

Since: 0.0.0.0

Choice typeclass

class Profunctor p => Choice p where Source #

Choice is a Profunctor that can be lifted to work with Either given input or some other value.

The other element of Either (variable of type c) can be of any type, and you can decide what type it should be. This is convenient for implementing various functions. E.g. prism uses this fact.

Assuming, we have the following functions in scope:

swapEither  :: Either a b -> Either b a
unnestLeft  :: Either (Either a b) c -> Either a (Either b c)
unnestRight :: Either a (Either b c) -> Either (Either a b) c

Instances of Choice should satisfy the following laws:

Since: 0.0.0.0

Methods

left :: p a b -> p (Either a c) (Either b c) Source #

right :: p a b -> p (Either c a) (Either c b) Source #

Instances

Instances details
Choice (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

left :: Forget r a b -> Forget r (Either a c) (Either b c) Source #

right :: Forget r a b -> Forget r (Either c a) (Either c b) Source #

Applicative m => Choice (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

left :: Fun m a b -> Fun m (Either a c) (Either b c) Source #

right :: Fun m a b -> Fun m (Either c a) (Either c b) Source #

Choice ((->) :: Type -> Type -> Type) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

left :: (a -> b) -> Either a c -> Either b c Source #

right :: (a -> b) -> Either c a -> Either c b Source #

Prism functions

prism Source #

Arguments

:: (b -> target)

Constructor

-> (source -> Either target a)

Matching function

-> Prism source target a b 

Create Prism from constructor and matching function.

Since: 0.0.0.0

prism' Source #

Arguments

:: (a -> source)

Constructor

-> (source -> Maybe a)

Matching function

-> Prism' source a 

Create monomorphic Prism' from constructor and matching function.

Since: 0.0.0.0

preview Source #

Arguments

:: forall a source p. p ~ Forget a 
=> Optic p source source a a

Optic that can be prism

-> source

Object (possible sum type)

-> Maybe a

Value of type a from a specific constructor

Match a value from source type.

Since: 0.0.0.0

Standard Prisms

_Just :: Prism (Maybe a) (Maybe b) a b Source #

Prism for a Just of Maybe.

>>> preview _Just (Just 42)
Just 42
>>> preview _Just Nothing
Nothing

Since: 0.0.0.0

_Left :: Prism (Either a x) (Either b x) a b Source #

Prism for a Left of Either.

>>> preview _Left (Left 42)
Just 42
>>> preview _Left (Right "Hello")
Nothing

Since: 0.0.0.0

_Right :: Prism (Either x a) (Either x b) a b Source #

Prism for a Left of Either.

>>> preview _Right (Left 42)
Nothing
>>> preview _Right (Right "Hello")
Just "Hello"

Since: 0.0.0.0

Traversals

Traversal types

type Traversal source target a b = forall p. (Choice p, Monoidal p) => Optic p source target a b Source #

Traversal provides composable ways to visit different parts of a data structure.

Traversal is an Optic p with the Choice and Monoidal constraints on the p type variable.

               +---> Current collection
               |
               |      +-> Final collection
               |      |
               +      +
type Traversal source target a b
                             + +
                             | |
          Current element <--+ |
                               |
         Final element <-------+

Since: 0.0.0.0

Monoidal typeclass

class Strong p => Monoidal p where Source #

Monoidal is Strong Profunctor that can be appended. It is similar to Monoids but for higher-kinded types.

Instances of Monoidal should satisfy the following laws:

⚠️ Note: The operator in the associativity law is equality ignoring the structure. The law is written in that way because pappend returns a tuple and the order of nested tuples depends on the order of pappend applications. In practice, this means, that if you want to check the law, you reorder tuples in the following way:

pappend f (pappend g h) ≡ dimap (\(a, (b, c)) -> ((a, b), c)) (\((a, b), c) -> (a, (b, c))) (pappend (pappend f g) h)

Since: 0.0.0.0

Methods

pappend :: p a b -> p c d -> p (a, c) (b, d) Source #

pempty :: p a a Source #

Instances

Instances details
Monoidal (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

pappend :: Forget r a b -> Forget r c d -> Forget r (a, c) (b, d) Source #

pempty :: Forget r a a Source #

Applicative m => Monoidal (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

pappend :: Fun m a b -> Fun m c d -> Fun m (a, c) (b, d) Source #

pempty :: Fun m a a Source #

Monoidal ((->) :: Type -> Type -> Type) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

pappend :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) Source #

pempty :: a -> a Source #

Traversal functions

traverseOf Source #

Arguments

:: (Applicative f, p ~ Fun f) 
=> Optic p source target a b

Optic that can be a traversal

-> (a -> f b)

Traversing function

-> source

Data structure to traverse

-> f target

Traversing result

Traverse a data structure using given Traversal.

>>> traverseOf eachPair putStrLn ("Hello", "World!")
Hello
World!
((),())

Since: 0.0.0.0

Standard traversals

eachPair :: Traversal (a, a) (b, b) a b Source #

Traversal for a pair of same type elements.

>>> over eachPair (+ 1) (3, 7)
(4,8)

Since: 0.0.0.0

eachMaybe :: Traversal (Maybe a) (Maybe b) a b Source #

Traversal for a Maybe.

>>> over eachMaybe (+ 1) (Just 3)
Just 4
>>> over eachMaybe (+ 1) Nothing
Nothing

Since: 0.0.0.0

eachList :: Traversal [a] [b] a b Source #

Traversal for lists.

>>> over eachList (+ 1) [1..5]
[2,3,4,5,6]
>>> over eachList (+ 1) []
[]

Since: 0.0.0.0

Internal data types

newtype Forget r a b Source #

Newtype around function a -> r. It's called forget because it forgets about its last type variable.

Since: 0.0.0.0

Constructors

Forget 

Fields

Instances

Instances details
Monoidal (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

pappend :: Forget r a b -> Forget r c d -> Forget r (a, c) (b, d) Source #

pempty :: Forget r a a Source #

Choice (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

left :: Forget r a b -> Forget r (Either a c) (Either b c) Source #

right :: Forget r a b -> Forget r (Either c a) (Either c b) Source #

Strong (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

first :: Forget r a b -> Forget r (a, c) (b, c) Source #

second :: Forget r a b -> Forget r (c, a) (c, b) Source #

Profunctor (Forget r) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

dimap :: (in2 -> in1) -> (out1 -> out2) -> Forget r in1 out1 -> Forget r in2 out2 Source #

Functor (Forget r x) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

fmap :: (a -> b) -> Forget r x a -> Forget r x b #

(<$) :: a -> Forget r x b -> Forget r x a #

newtype Fun m a b Source #

Fun m a b is a wrapper for function a -> m b.

Since: 0.0.0.0

Constructors

Fun 

Fields

Instances

Instances details
Applicative m => Monoidal (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

pappend :: Fun m a b -> Fun m c d -> Fun m (a, c) (b, d) Source #

pempty :: Fun m a a Source #

Applicative m => Choice (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

left :: Fun m a b -> Fun m (Either a c) (Either b c) Source #

right :: Fun m a b -> Fun m (Either c a) (Either c b) Source #

Functor m => Strong (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

first :: Fun m a b -> Fun m (a, c) (b, c) Source #

second :: Fun m a b -> Fun m (c, a) (c, b) Source #

Functor m => Profunctor (Fun m) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

dimap :: (in2 -> in1) -> (out1 -> out2) -> Fun m in1 out1 -> Fun m in2 out2 Source #

Functor m => Functor (Fun m x) Source #

Since: 0.0.0.0

Instance details

Defined in Prolens

Methods

fmap :: (a -> b) -> Fun m x a -> Fun m x b #

(<$) :: a -> Fun m x b -> Fun m x a #