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.Core

Description

 

Documentation

type Optic c s t a b = OpticC c (a, b) (s, t) Source #

data OpticC c x y where Source #

Constructors

Equality :: OpticC c q q 
OpticC :: c s t a b -> Optic c s t a b 

Instances

Optical c => Category * (OpticC c) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Category * (OpticC ReviewTrait) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Category * (OpticC IsoTrait) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

class Category (OpticC c) => Optical c where Source #

Minimal complete definition

cloneOptic, (∘)

Associated Types

type OptDens c (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens c ζ => c s t a b -> ζ s t a b Source #

(∘) :: c x y s t -> c s t a b -> c x y a b Source #

Instances

Optical FoldTrait Source # 

Associated Types

type OptDens (FoldTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens FoldTrait ζ => FoldTrait s t a b -> ζ s t a b Source #

(∘) :: FoldTrait x y s t -> FoldTrait s t a b -> FoldTrait x y a b Source #

Optical SetterTrait Source # 

Associated Types

type OptDens (SetterTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens SetterTrait ζ => SetterTrait s t a b -> ζ s t a b Source #

(∘) :: SetterTrait x y s t -> SetterTrait s t a b -> SetterTrait x y a b Source #

Optical TraversalTrait Source # 

Associated Types

type OptDens (TraversalTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens TraversalTrait ζ => TraversalTrait s t a b -> ζ s t a b Source #

(∘) :: TraversalTrait x y s t -> TraversalTrait s t a b -> TraversalTrait x y a b Source #

Optical GetterTrait Source # 

Associated Types

type OptDens (GetterTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens GetterTrait ζ => GetterTrait s t a b -> ζ s t a b Source #

(∘) :: GetterTrait x y s t -> GetterTrait s t a b -> GetterTrait x y a b Source #

Optical PrismTrait Source # 

Associated Types

type OptDens (PrismTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens PrismTrait ζ => PrismTrait s t a b -> ζ s t a b Source #

(∘) :: PrismTrait x y s t -> PrismTrait s t a b -> PrismTrait x y a b Source #

Optical LensTrait Source # 

Associated Types

type OptDens (LensTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens LensTrait ζ => LensTrait s t a b -> ζ s t a b Source #

(∘) :: LensTrait x y s t -> LensTrait s t a b -> LensTrait x y a b Source #

data IsoTrait s t a b Source #

Constructors

Iso (s -> a) (b -> t) 

Instances

FromIso IsoTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> IsoTrait s t a b Source #

Category * (OpticC IsoTrait) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

type AnIso s t a b = Optic IsoTrait s t a b Source #

type Iso s t a b = forall c. FromIso c => Optic c s t a b Source #

class FromIso c where Source #

Minimal complete definition

iso

Methods

iso :: (s -> a) -> (b -> t) -> c s t a b Source #

Instances

FromIso FoldTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> FoldTrait s t a b Source #

FromIso SetterTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> SetterTrait s t a b Source #

FromIso TraversalTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> TraversalTrait s t a b Source #

FromIso ReviewTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> ReviewTrait s t a b Source #

FromIso GetterTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> GetterTrait s t a b Source #

FromIso PrismTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> PrismTrait s t a b Source #

FromIso LensTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> LensTrait s t a b Source #

FromIso IsoTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> IsoTrait s t a b Source #

data LensTrait s t a b Source #

Constructors

Lens (s -> a) (s -> b -> t) 

Instances

FromLens LensTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> LensTrait s t a b Source #

FromIso LensTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> LensTrait s t a b Source #

Optical LensTrait Source # 

Associated Types

type OptDens (LensTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens LensTrait ζ => LensTrait s t a b -> ζ s t a b Source #

(∘) :: LensTrait x y s t -> LensTrait s t a b -> LensTrait x y a b Source #

type OptDens LensTrait ζ Source # 

type ALens s t a b = Optic LensTrait s t a b Source #

type Lens s t a b = forall c. FromLens c => Optic c s t a b Source #

class FromIso c => FromLens c where Source #

Minimal complete definition

lens

Methods

lens :: (s -> a) -> (s -> b -> t) -> c s t a b Source #

Instances

FromLens FoldTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> FoldTrait s t a b Source #

FromLens SetterTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> SetterTrait s t a b Source #

FromLens TraversalTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> TraversalTrait s t a b Source #

FromLens GetterTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> GetterTrait s t a b Source #

FromLens LensTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> LensTrait s t a b Source #

data PrismTrait s t a b Source #

Constructors

Prism (b -> t) (s -> Either t a) 

Instances

FromPrism PrismTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> PrismTrait s t a b Source #

FromIso PrismTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> PrismTrait s t a b Source #

Optical PrismTrait Source # 

Associated Types

type OptDens (PrismTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens PrismTrait ζ => PrismTrait s t a b -> ζ s t a b Source #

(∘) :: PrismTrait x y s t -> PrismTrait s t a b -> PrismTrait x y a b Source #

type OptDens PrismTrait ζ Source # 

type APrism s t a b = Optic PrismTrait s t a b Source #

type Prism s t a b = forall c. FromPrism c => Optic c s t a b Source #

class FromIso c => FromPrism c where Source #

Minimal complete definition

prism

Methods

prism :: (b -> t) -> (s -> Either t a) -> c s t a b Source #

Instances

FromPrism FoldTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> FoldTrait s t a b Source #

FromPrism SetterTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> SetterTrait s t a b Source #

FromPrism TraversalTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> TraversalTrait s t a b Source #

FromPrism ReviewTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> ReviewTrait s t a b Source #

FromPrism PrismTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> PrismTrait s t a b Source #

data GetterTrait s t a b Source #

Constructors

Getter (s -> a) 

Instances

FromGetter GetterTrait Source # 

Methods

to :: (s -> a) -> GetterTrait s t a b Source #

FromLens GetterTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> GetterTrait s t a b Source #

FromIso GetterTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> GetterTrait s t a b Source #

Optical GetterTrait Source # 

Associated Types

type OptDens (GetterTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens GetterTrait ζ => GetterTrait s t a b -> ζ s t a b Source #

(∘) :: GetterTrait x y s t -> GetterTrait s t a b -> GetterTrait x y a b Source #

type OptDens GetterTrait ζ Source # 

type AGetter s a = Optic GetterTrait s s a a Source #

type Getter s t a b = forall c. FromGetter c => Optic c s t a b Source #

class FromLens c => FromGetter c where Source #

Minimal complete definition

to

Methods

to :: (s -> a) -> c s t a b Source #

Instances

FromGetter FoldTrait Source # 

Methods

to :: (s -> a) -> FoldTrait s t a b Source #

FromGetter GetterTrait Source # 

Methods

to :: (s -> a) -> GetterTrait s t a b Source #

data ReviewTrait s t a b Source #

Constructors

Review (b -> t) 

Instances

FromReview ReviewTrait Source # 

Methods

unto :: (b -> t) -> ReviewTrait s t a b Source #

FromPrism ReviewTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> ReviewTrait s t a b Source #

FromIso ReviewTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> ReviewTrait s t a b Source #

Category * (OpticC ReviewTrait) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

type AReview b t = Optic ReviewTrait t t b b Source #

type Review s t a b = forall c. FromReview c => Optic c s t a b Source #

class FromPrism c => FromReview c where Source #

Minimal complete definition

unto

Methods

unto :: (b -> t) -> c s t a b Source #

Instances

FromReview ReviewTrait Source # 

Methods

unto :: (b -> t) -> ReviewTrait s t a b Source #

data TraversalTrait s t a b Source #

Constructors

Traversal (forall f. Applicative f => (a -> f b) -> s -> f t) 

Instances

FromTraversal TraversalTrait Source # 

Methods

traversed :: (forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t) -> TraversalTrait s t a b Source #

FromPrism TraversalTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> TraversalTrait s t a b Source #

FromLens TraversalTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> TraversalTrait s t a b Source #

FromIso TraversalTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> TraversalTrait s t a b Source #

Optical TraversalTrait Source # 

Associated Types

type OptDens (TraversalTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens TraversalTrait ζ => TraversalTrait s t a b -> ζ s t a b Source #

(∘) :: TraversalTrait x y s t -> TraversalTrait s t a b -> TraversalTrait x y a b Source #

type OptDens TraversalTrait ζ Source # 

type ATraversal s t a b = Optic TraversalTrait s t a b Source #

type Traversal s t a b = forall c. FromTraversal c => Optic c s t a b Source #

class (FromLens c, FromPrism c) => FromTraversal c where Source #

Minimal complete definition

traversed

Methods

traversed :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> c s t a b Source #

Instances

FromTraversal FoldTrait Source # 

Methods

traversed :: (forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t) -> FoldTrait s t a b Source #

FromTraversal SetterTrait Source # 

Methods

traversed :: (forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t) -> SetterTrait s t a b Source #

FromTraversal TraversalTrait Source # 

Methods

traversed :: (forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t) -> TraversalTrait s t a b Source #

data SetterTrait s t a b Source #

Constructors

Setter ((a -> b) -> s -> t) 

Instances

FromSetter SetterTrait Source # 

Methods

sets :: ((a -> b) -> s -> t) -> SetterTrait s t a b Source #

FromTraversal SetterTrait Source # 

Methods

traversed :: (forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t) -> SetterTrait s t a b Source #

FromPrism SetterTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> SetterTrait s t a b Source #

FromLens SetterTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> SetterTrait s t a b Source #

FromIso SetterTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> SetterTrait s t a b Source #

Optical SetterTrait Source # 

Associated Types

type OptDens (SetterTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens SetterTrait ζ => SetterTrait s t a b -> ζ s t a b Source #

(∘) :: SetterTrait x y s t -> SetterTrait s t a b -> SetterTrait x y a b Source #

type OptDens SetterTrait ζ Source # 

type ASetter s t a b = Optic SetterTrait s t a b Source #

type Setter s t a b = forall c. FromSetter c => Optic c s t a b Source #

class FromTraversal c => FromSetter c where Source #

Minimal complete definition

sets

Methods

sets :: ((a -> b) -> s -> t) -> c s t a b Source #

Instances

FromSetter SetterTrait Source # 

Methods

sets :: ((a -> b) -> s -> t) -> SetterTrait s t a b Source #

data FoldTrait s t a b Source #

Constructors

Fold (forall r. Monoid r => (a -> r) -> s -> r) 

Instances

FromFold FoldTrait Source # 

Methods

folds :: (forall r. Monoid r => (a -> r) -> s -> r) -> FoldTrait s t a b Source #

folded :: Foldable f => FoldTrait (f a) t a b Source #

FromTraversal FoldTrait Source # 

Methods

traversed :: (forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t) -> FoldTrait s t a b Source #

FromGetter FoldTrait Source # 

Methods

to :: (s -> a) -> FoldTrait s t a b Source #

FromPrism FoldTrait Source # 

Methods

prism :: (b -> t) -> (s -> Either t a) -> FoldTrait s t a b Source #

FromLens FoldTrait Source # 

Methods

lens :: (s -> a) -> (s -> b -> t) -> FoldTrait s t a b Source #

FromIso FoldTrait Source # 

Methods

iso :: (s -> a) -> (b -> t) -> FoldTrait s t a b Source #

Optical FoldTrait Source # 

Associated Types

type OptDens (FoldTrait :: * -> * -> * -> * -> *) (ζ :: * -> * -> * -> * -> *) :: Constraint Source #

Methods

cloneOptic :: OptDens FoldTrait ζ => FoldTrait s t a b -> ζ s t a b Source #

(∘) :: FoldTrait x y s t -> FoldTrait s t a b -> FoldTrait x y a b Source #

type OptDens FoldTrait ζ Source # 

type AFold s t a b = Optic FoldTrait s t a b Source #

type Fold s t a b = forall c. FromFold c => Optic c s t a b Source #

class FromTraversal c => FromFold c where Source #

Minimal complete definition

folds

Methods

folds :: (forall r. Monoid r => (a -> r) -> s -> r) -> c s t a b Source #

folded :: Foldable f => c (f a) t a b Source #

Instances

FromFold FoldTrait Source # 

Methods

folds :: (forall r. Monoid r => (a -> r) -> s -> r) -> FoldTrait s t a b Source #

folded :: Foldable f => FoldTrait (f a) t a b Source #