vitrea-0.1.0.0: Profunctor optics via the profunctor representation theorem.

Copyright(c) Mario Román 2020
LicenseGPL-3
Maintainermromang08@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Combinators

Description

Provides combinators for the library of optics in terms of Tambara modules.

Synopsis

Documentation

newtype Viewing a b s t Source #

Viewing is a profunctor that can be used to implement a view operation. Viewing is a Tambara module for all the optics that admit the view operator.

Constructors

Viewing 

Fields

Instances
Monad m => Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Algebra m :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Viewing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Algebra m w) => Viewing a b x y -> Viewing a b (w, x) (w, y) Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Viewing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Viewing a b x y -> Viewing a b (w, x) (w, y) Source #

Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Viewing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Viewing a b x1 y1 -> Viewing a b x2 y2 Source #

newtype Previewing a b s t Source #

Previewing is a profunctor that can be used to implement a preview operation. Previewing is a Tambara module for all the optics that admit the preview operator.

Constructors

Previewing 

Fields

Instances
Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Either Void Either Either (Previewing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Previewing a b x y -> Previewing a b (Either w x) (Either w y) Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Previewing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Previewing a b x y -> Previewing a b (w, x) (w, y) Source #

Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Previewing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Previewing a b x1 y1 -> Previewing a b x2 y2 Source #

newtype Setting a b s t Source #

Setting is a Tambara module for all the optics that admit the set operator.

Constructors

Setting 

Fields

  • getSet :: (a -> b) -> s -> t
     
Instances
Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Either Void Either Either (Setting a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Setting a b x y -> Setting a b (Either w x) (Either w y) Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Setting a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Setting a b x y -> Setting a b (w, x) (w, y) Source #

Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Setting a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Setting a b x1 y1 -> Setting a b x2 y2 Source #

newtype Classifying m a b s t Source #

Classifying is a Tambara module for all the optics that admit the classify operator.

Constructors

Classifying 

Fields

Instances
Monad m => Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Algebra m :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Classifying m a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Algebra m w) => Classifying m a b x y -> Classifying m a b (w, x) (w, y) Source #

Monad m => Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Classifying m a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Classifying m a b x1 y1 -> Classifying m a b x2 y2 Source #

newtype Aggregating a b s t Source #

Aggregating is a Tambara module for the optics that admit an aggregate operator.

Constructors

Aggregate 

Fields

Instances
Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Algebra []) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Aggregating a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Algebra [] w) => Aggregating a b x y -> Aggregating a b (w, x) (w, y) Source #

Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Aggregating a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Aggregating a b x1 y1 -> Aggregating a b x2 y2 Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Applicative (Nat :: (Type -> Type) -> (Type -> Type) -> Type) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Identity (App :: (Type -> Type) -> Type -> Type) (App :: (Type -> Type) -> Type -> Type) (Aggregating a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Applicative w) => Aggregating a b x y -> Aggregating a b (App w x) (App w y) Source #

newtype Updating m a b s t Source #

Updating is a Tambara module for the optics admitting an update operator.

Constructors

Update 

Fields

Instances
Monad m => Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) (Kleisli m :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Updating m a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Updating m a b x y -> Updating m a b (w, x) (w, y) Source #

Monad m => Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Updating m a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Updating m a b x1 y1 -> Updating m a b x2 y2 Source #

Monad m => Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) (Kleisli m :: Type -> Type -> Type) (Updating m a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> Kleisli m y1 y2 -> Updating m a b x1 y1 -> Updating m a b x2 y2 Source #

newtype Replacing a b s t Source #

Replacing is a Tambara module for the optics admitting an over operator.

Constructors

Replace 

Fields

Instances
Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Either Void Either Either (Replacing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Replacing a b x y -> Replacing a b (Either w x) (Either w y) Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Replacing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Any w) => Replacing a b x y -> Replacing a b (w, x) (w, y) Source #

Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Replacing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Replacing a b x1 y1 -> Replacing a b x2 y2 Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Functor (Nat :: (Type -> Type) -> (Type -> Type) -> Type) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Identity (App :: (Type -> Type) -> Type -> Type) (App :: (Type -> Type) -> Type -> Type) (Replacing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Functor w) => Replacing a b x y -> Replacing a b (App w x) (App w y) Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Applicative (Nat :: (Type -> Type) -> (Type -> Type) -> Type) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Identity (App :: (Type -> Type) -> Type -> Type) (App :: (Type -> Type) -> Type -> Type) (Replacing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Applicative w) => Replacing a b x y -> Replacing a b (App w x) (App w y) Source #

Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Traversable (Nat :: (Type -> Type) -> (Type -> Type) -> Type) (Compose :: (Type -> Type) -> (Type -> Type) -> Type -> Type) Identity (App :: (Type -> Type) -> Type -> Type) (App :: (Type -> Type) -> Type -> Type) (Replacing a b :: Type -> Type -> Type) Source # 
Instance details

Defined in Combinators

Methods

tambara :: (Any x, Any y, Traversable w) => Replacing a b x y -> Replacing a b (App w x) (App w y) Source #

(^.) :: s -> (Viewing a b a b -> Viewing a b s t) -> a infixl 8 Source #

Inspired by the "view" operator of Kmett et al's lens library. The fixity and semantics are such that subsequent field accesses can be performed with ..

(?.) :: s -> (Previewing a b a b -> Previewing a b s t) -> Maybe a infixl 8 Source #

Inspired by the "preview" operator of Kmett et al's lens library. The fixity and semantics are such that subsequent field accesses can be performed with ..

(.~) :: (Setting a b a b -> Setting a b s t) -> b -> s -> t infixl 8 Source #

Inspired by the "set" operator of Kmett et al's lens library. The fixity and semantics are such that subsequent field accesses can be performed with ..

(%~) :: (Replacing a b a b -> Replacing a b s t) -> (a -> b) -> s -> t infixl 8 Source #

Inspired by the "over" operator of Kmett et al's lens library. The fixity and semantics are such that subsequent field accesses can be performed with ..

(.?) :: Monad m => (Classifying m a b a b -> Classifying m a b s t) -> b -> m s -> t infixl 8 Source #

A "classify" operator. The fixity and semantics are such that subsequent field accesses can be performed with ..

(>-) :: (Aggregating a b a b -> Aggregating a b s t) -> ([a] -> b) -> [s] -> t infixl 8 Source #

An "aggregate" operator. The fixity and semantics are such that subsequent field accesses can be performed with ..

mupdate :: Monad m => (Updating m a b a b -> Updating m a b s t) -> b -> s -> m t Source #

An "mupdate" operator. It is prepared to be used with do notation.