mezzolens-0.0.0: Pure Profunctor Functional Lenses

Safe HaskellSafe
LanguageHaskell2010

Mezzolens

Synopsis

Documentation

set :: ((a -> b) -> c) -> b -> c Source

set :: SEC ta tb a b -> b -> ta -> tb

modifyF :: Optical (SubStar f) ta tb a b -> (a -> f b) -> ta -> f tb Source

modifyF :: Functor f => Lens ta tb a b -> (a -> f b) -> ta -> f tb
modifyF :: Applicative f => Traversal ta tb a b -> (a -> f b) -> ta -> f tb

match :: Optical (SubStar (Either a)) ta tb a b -> ta -> Either tb a Source

match :: Traversal ta tb a b -> ta -> Either tb a

get :: Optical (SubStar (Constant a)) ta tb a b -> ta -> a Source

get :: To ta tb a b -> ta -> a
get :: Monoid a => Fold ta tb a b -> ta -> a

gets :: Optical (SubStar (Constant r)) ta tb a b -> (a -> r) -> ta -> r Source

gets :: To ta tb a b -> (a -> r) -> ta -> r
gets :: Monoid r => Fold ta tb a b -> (a -> r) -> ta -> r

beget :: Optical (SuperStar (Constant b)) ta tb a b -> b -> tb Source

beget :: Fro ta tb a b -> b -> tb

toListOf :: Applicative f => Optical (SubStar (Constant (f a))) ta tb a b -> ta -> f a Source

toListOf :: Fold ta tb a b -> ta -> [a]
toListOf :: (Applicative f, Monoid (f a)) => Fold ta tb a b -> ta -> f a
toListOf :: Applicative f => To ta tb a b -> ta -> f a

firstOf :: Optical (SubStar (Constant (First a))) ta tb a b -> ta -> Maybe a Source

firstOf :: Fold ta tb a b -> ta -> Maybe a

sumOf :: Optical (SubStar (Constant (Sum a))) ta tb a b -> ta -> a Source

productOf :: Optical (SubStar (Constant (Product a))) ta tb a b -> ta -> a Source

allOf :: Optical (SubStar (Constant All)) ta tb a b -> (a -> Bool) -> ta -> Bool Source

anyOf :: Optical (SubStar (Constant Any)) ta tb a b -> (a -> Bool) -> ta -> Bool Source

lengthOf :: Num r => Optical (SubStar (Constant (Sum r))) ta tb a b -> ta -> r Source

nullOf :: Optical (SubStar (Constant All)) ta tb a b -> ta -> Bool Source

to :: (ta -> a) -> To ta tb a b Source

fro :: (b -> tb) -> Fro ta tb a b Source

un :: Optical (ProProduct (SubStar (Constant tb)) (SuperStar (Constant ta))) b a tb ta -> Iso ta tb a b Source

un :: Iso b a tb ta -> Iso ta tb a b

alongside :: Profunctor p => Optical (AlongSide p sc sd) ta tb a b -> Optical (AlongSide p a b) sc sd c d -> Optical p (ta, sc) (tb, sd) (a, c) (b, d) Source

alongside :: Iso ta tb a b -> Iso sc sd c d -> Iso (ta,sc) (tb,sd) (a,c) (b,d)
alongside :: Lens ta tb a b -> Lens sc sd c d -> Lens (ta,sc) (tb,sd) (a,c) (b,d)
alongside :: To ta tb a b -> To sc sd c d -> To (ta,sc) (tb,sd) (a,c) (b,d)

eitherside :: Profunctor p => Optical (EitherSide p sc sd) ta tb a b -> Optical (EitherSide p a b) sc sd c d -> Optical p (Either ta sc) (Either tb sd) (Either a c) (Either b d) Source

eitherside :: Iso ta tb a b -> Iso sc sd c d -> Iso (Either ta sc) (Either tb sd) (Either a c) (Either b d)
eitherside :: Prism ta tb a b -> Prism sc sd c d -> Lens (Either ta sc) (Either tb sd) (Either a c) (Either b d)
eitherside :: Fro ta tb a b -> Fro sc sd c d -> To (Either ta sc) (Either tb sd) (Either a c) (Either b d)

(^.) :: ta -> Optical (SubStar (Constant a)) ta tb a b -> a infixl 8 Source

(^..) :: Applicative f => ta -> Optical (SubStar (Constant (f a))) ta tb a b -> f a infixl 8 Source

(^?) :: ta -> Optical (SubStar (Constant (First a))) ta tb a b -> Maybe a infixl 8 Source

(.~) :: ((a -> b) -> c) -> b -> c infixr 4 Source

data SuperStar f a b Source

Instances

Phantom f => InPhantom (SuperStar f) Source 
Phantom f => Choice (SuperStar f) Source 
Functor f => Profunctor (SuperStar f) Source 

data Constant a b :: * -> * -> *

Constant functor.

Instances

Functor (Constant a) 
Monoid a => Applicative (Constant a) 
Foldable (Constant a) 
Traversable (Constant a) 
Eq a => Eq1 (Constant a) 
Ord a => Ord1 (Constant a) 
Read a => Read1 (Constant a) 
Show a => Show1 (Constant a) 
Eq a => Eq (Constant a b) 
Ord a => Ord (Constant a b) 
Read a => Read (Constant a b) 
Show a => Show (Constant a b) 

data First a :: * -> *

Maybe monoid returning the leftmost non-Nothing value.

First a is isomorphic to Alt Maybe a, but precedes it historically.

Instances

Monad First 
Functor First 
Applicative First 
Generic1 First 
Eq a => Eq (First a) 
Ord a => Ord (First a) 
Read a => Read (First a) 
Show a => Show (First a) 
Generic (First a) 
Monoid (First a) 
type Rep1 First = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec1 Maybe))) 
type Rep (First a) = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec0 (Maybe a)))) 

data Sum a :: * -> *

Monoid under addition.

Instances

Generic1 Sum 
Bounded a => Bounded (Sum a) 
Eq a => Eq (Sum a) 
Num a => Num (Sum a) 
Ord a => Ord (Sum a) 
Read a => Read (Sum a) 
Show a => Show (Sum a) 
Generic (Sum a) 
Num a => Monoid (Sum a) 
type Rep1 Sum = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum Par1)) 
type Rep (Sum a) = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum (Rec0 a))) 

data Product a :: * -> *

Monoid under multiplication.

Instances

Generic1 Product 
Bounded a => Bounded (Product a) 
Eq a => Eq (Product a) 
Num a => Num (Product a) 
Ord a => Ord (Product a) 
Read a => Read (Product a) 
Show a => Show (Product a) 
Generic (Product a) 
Num a => Monoid (Product a) 
type Rep1 Product = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product Par1)) 
type Rep (Product a) = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product (Rec0 a))) 

data All :: *

Boolean monoid under conjunction (&&).

Instances

Bounded All 
Eq All 
Ord All 
Read All 
Show All 
Generic All 
Monoid All 
type Rep All = D1 D1All (C1 C1_0All (S1 S1_0_0All (Rec0 Bool))) 

data Any :: *

Boolean monoid under disjunction (||).

Instances

Bounded Any 
Eq Any 
Ord Any 
Read Any 
Show Any 
Generic Any 
Monoid Any 
type Rep Any = D1 D1Any (C1 C1_0Any (S1 S1_0_0Any (Rec0 Bool))) 

data AlongSide p c d a b Source

data EitherSide p c d a b Source