lens-3.7.4: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.Classes

Contents

Description

 

Synopsis

Getters

class Functor f => Gettable f whereSource

Generalizing Const so we can apply simple Applicative transformations to it and so we can get nicer error messages

A Gettable Functor ignores its argument, which it carries solely as a phantom type parameter.

To ensure this, an instance of Gettable is required to satisfy:

id = fmap f = coerce

Which is equivalent to making a Gettable f an "anyvariant" functor.

Methods

coerce :: f a -> f bSource

Replace the phantom type argument.

noEffect :: (Applicative f, Gettable f) => f aSource

The mempty equivalent for a Gettable Applicative Functor.

Actions

class (Monad m, Gettable f) => Effective m r f | f -> m r whereSource

An Effective Functor ignores its argument and is isomorphic to a Monad wrapped around a value.

That said, the Monad is possibly rather unrelated to any Applicative structure.

Methods

effective :: m r -> f aSource

ineffective :: f a -> m rSource

Instances

Effective Identity r (Accessor r) 
Monad m => Effective m r (Effect m r) 
Effective m r f => Effective m (Dual r) (Backwards f) 

Setters

class Applicative f => Settable f whereSource

Anything Settable must be isomorphic to the Identity Functor.

Methods

untainted :: f a -> aSource

untainted# :: (a -> f b) -> a -> bSource

tainted# :: (a -> b) -> a -> f bSource

Instances

Settable Identity

so you can pass our a Setter into combinators from other lens libraries

Settable Mutator 
Settable f => Settable (Backwards f)

backwards

(Settable f, Settable g) => Settable (Compose f g) 

Isomorphisms

class Category k => Isomorphic k whereSource

Used to provide overloading of isomorphism application

An instance of Isomorphic is a Category with a canonical mapping to it from the category of isomorphisms over Haskell types.

Methods

iso :: Functor f => (s -> a) -> (b -> t) -> k (a -> f b) (s -> f t)Source

Build a simple isomorphism from a pair of inverse functions

 view (iso f g) ≡ f
 view (from (iso f g)) ≡ g
 set (iso f g) h ≡ g . h . f
 set (from (iso f g)) h ≡ f . h . g

Prisms

class Isomorphic k => Prismatic k whereSource

Used to provide overloading of prisms.

An instance of Prismatic is a Category with a canonical mapping to it from the category of embedding-projection pairs over Haskell types.

Methods

prism :: Applicative f => (b -> t) -> (s -> Either t a) -> k (a -> f b) (s -> f t)Source

Build a Prism.

Either t a is used instead of Maybe a to permit the types of s and t to differ.

Instances

Indexable

class Indexable i k whereSource

This class permits overloading of function application for things that also admit a notion of a key or index.

Methods

indexed :: ((i -> a) -> b) -> k a bSource

Build a function from an Indexed function

Instances

Indexable i (->) 
~ * i j => Indexable i (Indexed j)

Using an equality witness to avoid potential overlapping instances and aid dispatch.