indexed-profunctors-0.1: Utilities for indexed profunctors

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Indexed

Contents

Description

Definitions of concrete profunctors and profunctor classes.

Synopsis

Profunctor classes

class Profunctor p where Source #

Minimal complete definition

dimap, lmap, rmap

Methods

dimap :: (a -> b) -> (c -> d) -> p i b c -> p i a d Source #

lmap :: (a -> b) -> p i b c -> p i a c Source #

rmap :: (c -> d) -> p i b c -> p i b d Source #

lcoerce' :: Coercible a b => p i a c -> p i b c Source #

lcoerce' :: Coercible (p i a c) (p i b c) => p i a c -> p i b c Source #

rcoerce' :: Coercible a b => p i c a -> p i c b Source #

rcoerce' :: Coercible (p i c a) (p i c b) => p i c a -> p i c b Source #

conjoined__ :: (p i a b -> p i s t) -> (p i a b -> p j s t) -> p i a b -> p j s t Source #

conjoined__ :: Coercible (p i s t) (p j s t) => (p i a b -> p i s t) -> (p i a b -> p j s t) -> p i a b -> p j s t Source #

ixcontramap :: (j -> i) -> p i a b -> p j a b Source #

ixcontramap :: Coercible (p i a b) (p j a b) => (j -> i) -> p i a b -> p j a b Source #

Instances
Profunctor Tagged Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged i b c -> Tagged i a d Source #

lmap :: (a -> b) -> Tagged i b c -> Tagged i a c Source #

rmap :: (c -> d) -> Tagged i b c -> Tagged i b d Source #

lcoerce' :: Coercible a b => Tagged i a c -> Tagged i b c Source #

rcoerce' :: Coercible a b => Tagged i c a -> Tagged i c b Source #

conjoined__ :: (Tagged i a b -> Tagged i s t) -> (Tagged i a b -> Tagged j s t) -> Tagged i a b -> Tagged j s t Source #

ixcontramap :: (j -> i) -> Tagged i a b -> Tagged j a b Source #

Profunctor IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxFunArrow i b c -> IxFunArrow i a d Source #

lmap :: (a -> b) -> IxFunArrow i b c -> IxFunArrow i a c Source #

rmap :: (c -> d) -> IxFunArrow i b c -> IxFunArrow i b d Source #

lcoerce' :: Coercible a b => IxFunArrow i a c -> IxFunArrow i b c Source #

rcoerce' :: Coercible a b => IxFunArrow i c a -> IxFunArrow i c b Source #

conjoined__ :: (IxFunArrow i a b -> IxFunArrow i s t) -> (IxFunArrow i a b -> IxFunArrow j s t) -> IxFunArrow i a b -> IxFunArrow j s t Source #

ixcontramap :: (j -> i) -> IxFunArrow i a b -> IxFunArrow j a b Source #

Profunctor FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> FunArrow i b c -> FunArrow i a d Source #

lmap :: (a -> b) -> FunArrow i b c -> FunArrow i a c Source #

rmap :: (c -> d) -> FunArrow i b c -> FunArrow i b d Source #

lcoerce' :: Coercible a b => FunArrow i a c -> FunArrow i b c Source #

rcoerce' :: Coercible a b => FunArrow i c a -> FunArrow i c b Source #

conjoined__ :: (FunArrow i a b -> FunArrow i s t) -> (FunArrow i a b -> FunArrow j s t) -> FunArrow i a b -> FunArrow j s t Source #

ixcontramap :: (j -> i) -> FunArrow i a b -> FunArrow j a b Source #

Functor f => Profunctor (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxStarA f i b c -> IxStarA f i a d Source #

lmap :: (a -> b) -> IxStarA f i b c -> IxStarA f i a c Source #

rmap :: (c -> d) -> IxStarA f i b c -> IxStarA f i b d Source #

lcoerce' :: Coercible a b => IxStarA f i a c -> IxStarA f i b c Source #

rcoerce' :: Coercible a b => IxStarA f i c a -> IxStarA f i c b Source #

conjoined__ :: (IxStarA f i a b -> IxStarA f i s t) -> (IxStarA f i a b -> IxStarA f j s t) -> IxStarA f i a b -> IxStarA f j s t Source #

ixcontramap :: (j -> i) -> IxStarA f i a b -> IxStarA f j a b Source #

Functor f => Profunctor (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> StarA f i b c -> StarA f i a d Source #

lmap :: (a -> b) -> StarA f i b c -> StarA f i a c Source #

rmap :: (c -> d) -> StarA f i b c -> StarA f i b d Source #

lcoerce' :: Coercible a b => StarA f i a c -> StarA f i b c Source #

rcoerce' :: Coercible a b => StarA f i c a -> StarA f i c b Source #

conjoined__ :: (StarA f i a b -> StarA f i s t) -> (StarA f i a b -> StarA f j s t) -> StarA f i a b -> StarA f j s t Source #

ixcontramap :: (j -> i) -> StarA f i a b -> StarA f j a b Source #

Profunctor (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxForgetM r i b c -> IxForgetM r i a d Source #

lmap :: (a -> b) -> IxForgetM r i b c -> IxForgetM r i a c Source #

rmap :: (c -> d) -> IxForgetM r i b c -> IxForgetM r i b d Source #

lcoerce' :: Coercible a b => IxForgetM r i a c -> IxForgetM r i b c Source #

rcoerce' :: Coercible a b => IxForgetM r i c a -> IxForgetM r i c b Source #

conjoined__ :: (IxForgetM r i a b -> IxForgetM r i s t) -> (IxForgetM r i a b -> IxForgetM r j s t) -> IxForgetM r i a b -> IxForgetM r j s t Source #

ixcontramap :: (j -> i) -> IxForgetM r i a b -> IxForgetM r j a b Source #

Profunctor (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxForget r i b c -> IxForget r i a d Source #

lmap :: (a -> b) -> IxForget r i b c -> IxForget r i a c Source #

rmap :: (c -> d) -> IxForget r i b c -> IxForget r i b d Source #

lcoerce' :: Coercible a b => IxForget r i a c -> IxForget r i b c Source #

rcoerce' :: Coercible a b => IxForget r i c a -> IxForget r i c b Source #

conjoined__ :: (IxForget r i a b -> IxForget r i s t) -> (IxForget r i a b -> IxForget r j s t) -> IxForget r i a b -> IxForget r j s t Source #

ixcontramap :: (j -> i) -> IxForget r i a b -> IxForget r j a b Source #

Functor f => Profunctor (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxStar f i b c -> IxStar f i a d Source #

lmap :: (a -> b) -> IxStar f i b c -> IxStar f i a c Source #

rmap :: (c -> d) -> IxStar f i b c -> IxStar f i b d Source #

lcoerce' :: Coercible a b => IxStar f i a c -> IxStar f i b c Source #

rcoerce' :: Coercible a b => IxStar f i c a -> IxStar f i c b Source #

conjoined__ :: (IxStar f i a b -> IxStar f i s t) -> (IxStar f i a b -> IxStar f j s t) -> IxStar f i a b -> IxStar f j s t Source #

ixcontramap :: (j -> i) -> IxStar f i a b -> IxStar f j a b Source #

Profunctor (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> ForgetM r i b c -> ForgetM r i a d Source #

lmap :: (a -> b) -> ForgetM r i b c -> ForgetM r i a c Source #

rmap :: (c -> d) -> ForgetM r i b c -> ForgetM r i b d Source #

lcoerce' :: Coercible a b => ForgetM r i a c -> ForgetM r i b c Source #

rcoerce' :: Coercible a b => ForgetM r i c a -> ForgetM r i c b Source #

conjoined__ :: (ForgetM r i a b -> ForgetM r i s t) -> (ForgetM r i a b -> ForgetM r j s t) -> ForgetM r i a b -> ForgetM r j s t Source #

ixcontramap :: (j -> i) -> ForgetM r i a b -> ForgetM r j a b Source #

Profunctor (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Forget r i b c -> Forget r i a d Source #

lmap :: (a -> b) -> Forget r i b c -> Forget r i a c Source #

rmap :: (c -> d) -> Forget r i b c -> Forget r i b d Source #

lcoerce' :: Coercible a b => Forget r i a c -> Forget r i b c Source #

rcoerce' :: Coercible a b => Forget r i c a -> Forget r i c b Source #

conjoined__ :: (Forget r i a b -> Forget r i s t) -> (Forget r i a b -> Forget r j s t) -> Forget r i a b -> Forget r j s t Source #

ixcontramap :: (j -> i) -> Forget r i a b -> Forget r j a b Source #

Functor f => Profunctor (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Star f i b c -> Star f i a d Source #

lmap :: (a -> b) -> Star f i b c -> Star f i a c Source #

rmap :: (c -> d) -> Star f i b c -> Star f i b d Source #

lcoerce' :: Coercible a b => Star f i a c -> Star f i b c Source #

rcoerce' :: Coercible a b => Star f i c a -> Star f i c b Source #

conjoined__ :: (Star f i a b -> Star f i s t) -> (Star f i a b -> Star f j s t) -> Star f i a b -> Star f j s t Source #

ixcontramap :: (j -> i) -> Star f i a b -> Star f j a b Source #

Profunctor (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> AffineMarket a b i b0 c -> AffineMarket a b i a0 d Source #

lmap :: (a0 -> b0) -> AffineMarket a b i b0 c -> AffineMarket a b i a0 c Source #

rmap :: (c -> d) -> AffineMarket a b i b0 c -> AffineMarket a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => AffineMarket a b i a0 c -> AffineMarket a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => AffineMarket a b i c a0 -> AffineMarket a b i c b0 Source #

conjoined__ :: (AffineMarket a b i a0 b0 -> AffineMarket a b i s t) -> (AffineMarket a b i a0 b0 -> AffineMarket a b j s t) -> AffineMarket a b i a0 b0 -> AffineMarket a b j s t Source #

ixcontramap :: (j -> i) -> AffineMarket a b i a0 b0 -> AffineMarket a b j a0 b0 Source #

Profunctor (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Market a b i b0 c -> Market a b i a0 d Source #

lmap :: (a0 -> b0) -> Market a b i b0 c -> Market a b i a0 c Source #

rmap :: (c -> d) -> Market a b i b0 c -> Market a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => Market a b i a0 c -> Market a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => Market a b i c a0 -> Market a b i c b0 Source #

conjoined__ :: (Market a b i a0 b0 -> Market a b i s t) -> (Market a b i a0 b0 -> Market a b j s t) -> Market a b i a0 b0 -> Market a b j s t Source #

ixcontramap :: (j -> i) -> Market a b i a0 b0 -> Market a b j a0 b0 Source #

Profunctor (Store a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Store a b i b0 c -> Store a b i a0 d Source #

lmap :: (a0 -> b0) -> Store a b i b0 c -> Store a b i a0 c Source #

rmap :: (c -> d) -> Store a b i b0 c -> Store a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => Store a b i a0 c -> Store a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => Store a b i c a0 -> Store a b i c b0 Source #

conjoined__ :: (Store a b i a0 b0 -> Store a b i s t) -> (Store a b i a0 b0 -> Store a b j s t) -> Store a b i a0 b0 -> Store a b j s t Source #

ixcontramap :: (j -> i) -> Store a b i a0 b0 -> Store a b j a0 b0 Source #

Profunctor (Exchange a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Exchange a b i b0 c -> Exchange a b i a0 d Source #

lmap :: (a0 -> b0) -> Exchange a b i b0 c -> Exchange a b i a0 c Source #

rmap :: (c -> d) -> Exchange a b i b0 c -> Exchange a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => Exchange a b i a0 c -> Exchange a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => Exchange a b i c a0 -> Exchange a b i c b0 Source #

conjoined__ :: (Exchange a b i a0 b0 -> Exchange a b i s t) -> (Exchange a b i a0 b0 -> Exchange a b j s t) -> Exchange a b i a0 b0 -> Exchange a b j s t Source #

ixcontramap :: (j -> i) -> Exchange a b i a0 b0 -> Exchange a b j a0 b0 Source #

lcoerce :: (Coercible a b, Profunctor p) => p i a c -> p i b c Source #

lcoerce' with type arguments rearranged for TypeApplications.

rcoerce :: (Coercible a b, Profunctor p) => p i c a -> p i c b Source #

rcoerce' with type arguments rearranged for TypeApplications.

class Profunctor p => Strong p where Source #

Minimal complete definition

first', second'

Methods

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

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

linear :: (forall f. Functor f => (a -> f b) -> s -> f t) -> p i a b -> p i s t Source #

ilinear :: (forall f. Functor f => (i -> a -> f b) -> s -> f t) -> p j a b -> p (i -> j) s t Source #

ilinear :: Coercible (p j s t) (p (i -> j) s t) => (forall f. Functor f => (i -> a -> f b) -> s -> f t) -> p j a b -> p (i -> j) s t Source #

Instances
Strong IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Strong FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> FunArrow i a b -> FunArrow i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

Functor f => Strong (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxStarA f i a b -> IxStarA f i (a, c) (b, c) Source #

second' :: IxStarA f i a b -> IxStarA f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> IxStarA f i a b -> IxStarA f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> IxStarA f j a b -> IxStarA f (i -> j) s t Source #

Functor f => Strong (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: StarA f i a b -> StarA f i (a, c) (b, c) Source #

second' :: StarA f i a b -> StarA f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> StarA f i a b -> StarA f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> StarA f j a b -> StarA f (i -> j) s t Source #

Strong (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxForgetM r i a b -> IxForgetM r i (a, c) (b, c) Source #

second' :: IxForgetM r i a b -> IxForgetM r i (c, a) (c, b) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> IxForgetM r i a b -> IxForgetM r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> IxForgetM r j a b -> IxForgetM r (i -> j) s t Source #

Strong (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxForget r i a b -> IxForget r i (a, c) (b, c) Source #

second' :: IxForget r i a b -> IxForget r i (c, a) (c, b) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> IxForget r i a b -> IxForget r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> IxForget r j a b -> IxForget r (i -> j) s t Source #

Functor f => Strong (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxStar f i a b -> IxStar f i (a, c) (b, c) Source #

second' :: IxStar f i a b -> IxStar f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> IxStar f i a b -> IxStar f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> IxStar f j a b -> IxStar f (i -> j) s t Source #

Strong (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: ForgetM r i a b -> ForgetM r i (a, c) (b, c) Source #

second' :: ForgetM r i a b -> ForgetM r i (c, a) (c, b) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> ForgetM r i a b -> ForgetM r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> ForgetM r j a b -> ForgetM r (i -> j) s t Source #

Strong (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> Forget r i a b -> Forget r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> Forget r j a b -> Forget r (i -> j) s t Source #

Functor f => Strong (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: Star f i a b -> Star f i (a, c) (b, c) Source #

second' :: Star f i a b -> Star f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> Star f i a b -> Star f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> Star f j a b -> Star f (i -> j) s t Source #

Strong (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (a0, c) (b0, c) Source #

second' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (c, a0) (c, b0) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a0 -> f b0) -> s -> f t) -> AffineMarket a b i a0 b0 -> AffineMarket a b i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a0 -> f b0) -> s -> f t) -> AffineMarket a b j a0 b0 -> AffineMarket a b (i -> j) s t Source #

Strong (Store a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: Store a b i a0 b0 -> Store a b i (a0, c) (b0, c) Source #

second' :: Store a b i a0 b0 -> Store a b i (c, a0) (c, b0) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a0 -> f b0) -> s -> f t) -> Store a b i a0 b0 -> Store a b i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a0 -> f b0) -> s -> f t) -> Store a b j a0 b0 -> Store a b (i -> j) s t Source #

class Profunctor p => Costrong p where Source #

Methods

unfirst :: p i (a, d) (b, d) -> p i a b Source #

unsecond :: p i (d, a) (d, b) -> p i a b Source #

Instances
Costrong Tagged Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unfirst :: Tagged i (a, d) (b, d) -> Tagged i a b Source #

unsecond :: Tagged i (d, a) (d, b) -> Tagged i a b Source #

class Profunctor p => Choice p where Source #

Methods

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

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

Instances
Choice Tagged Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Choice IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Choice FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Functor f => Choice (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxStarA f i a b -> IxStarA f i (Either a c) (Either b c) Source #

right' :: IxStarA f i a b -> IxStarA f i (Either c a) (Either c b) Source #

Functor f => Choice (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: StarA f i a b -> StarA f i (Either a c) (Either b c) Source #

right' :: StarA f i a b -> StarA f i (Either c a) (Either c b) Source #

Choice (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxForgetM r i a b -> IxForgetM r i (Either a c) (Either b c) Source #

right' :: IxForgetM r i a b -> IxForgetM r i (Either c a) (Either c b) Source #

Monoid r => Choice (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxForget r i a b -> IxForget r i (Either a c) (Either b c) Source #

right' :: IxForget r i a b -> IxForget r i (Either c a) (Either c b) Source #

Applicative f => Choice (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxStar f i a b -> IxStar f i (Either a c) (Either b c) Source #

right' :: IxStar f i a b -> IxStar f i (Either c a) (Either c b) Source #

Choice (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: ForgetM r i a b -> ForgetM r i (Either a c) (Either b c) Source #

right' :: ForgetM r i a b -> ForgetM r i (Either c a) (Either c b) Source #

Monoid r => Choice (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Applicative f => Choice (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: Star f i a b -> Star f i (Either a c) (Either b c) Source #

right' :: Star f i a b -> Star f i (Either c a) (Either c b) Source #

Choice (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (Either a0 c) (Either b0 c) Source #

right' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (Either c a0) (Either c b0) Source #

Choice (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: Market a b i a0 b0 -> Market a b i (Either a0 c) (Either b0 c) Source #

right' :: Market a b i a0 b0 -> Market a b i (Either c a0) (Either c b0) Source #

class Profunctor p => Cochoice p where Source #

Methods

unleft :: p i (Either a d) (Either b d) -> p i a b Source #

unright :: p i (Either d a) (Either d b) -> p i a b Source #

Instances
Cochoice (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: IxForgetM r i (Either a d) (Either b d) -> IxForgetM r i a b Source #

unright :: IxForgetM r i (Either d a) (Either d b) -> IxForgetM r i a b Source #

Cochoice (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: IxForget r i (Either a d) (Either b d) -> IxForget r i a b Source #

unright :: IxForget r i (Either d a) (Either d b) -> IxForget r i a b Source #

Cochoice (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: ForgetM r i (Either a d) (Either b d) -> ForgetM r i a b Source #

unright :: ForgetM r i (Either d a) (Either d b) -> ForgetM r i a b Source #

Cochoice (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: Forget r i (Either a d) (Either b d) -> Forget r i a b Source #

unright :: Forget r i (Either d a) (Either d b) -> Forget r i a b Source #

class (Choice p, Strong p) => Visiting p where Source #

Minimal complete definition

Nothing

Methods

visit :: forall i s t a b. (forall f. Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t) -> p i a b -> p i s t Source #

ivisit :: (forall f. Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t) -> p j a b -> p (i -> j) s t Source #

ivisit :: Coercible (p j s t) (p (i -> j) s t) => (forall f. Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t) -> p j a b -> p (i -> j) s t Source #

Instances
Visiting IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Visiting FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t) -> FunArrow i a b -> FunArrow i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

Functor f => Visiting (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> IxStarA f i a b -> IxStarA f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> IxStarA f j a b -> IxStarA f (i -> j) s t Source #

Functor f => Visiting (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> StarA f i a b -> StarA f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> StarA f j a b -> StarA f (i -> j) s t Source #

Visiting (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> IxForgetM r i a b -> IxForgetM r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> IxForgetM r j a b -> IxForgetM r (i -> j) s t Source #

Monoid r => Visiting (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> IxForget r i a b -> IxForget r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> IxForget r j a b -> IxForget r (i -> j) s t Source #

Applicative f => Visiting (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> IxStar f i a b -> IxStar f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> IxStar f j a b -> IxStar f (i -> j) s t Source #

Visiting (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> ForgetM r i a b -> ForgetM r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> ForgetM r j a b -> ForgetM r (i -> j) s t Source #

Monoid r => Visiting (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> Forget r i a b -> Forget r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> Forget r j a b -> Forget r (i -> j) s t Source #

Applicative f => Visiting (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> Star f i a b -> Star f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> Star f j a b -> Star f (i -> j) s t Source #

Visiting (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a0 -> f b0) -> s -> f t) -> AffineMarket a b i a0 b0 -> AffineMarket a b i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a0 -> f b0) -> s -> f t) -> AffineMarket a b j a0 b0 -> AffineMarket a b (i -> j) s t Source #

class Traversing p => Mapping p where Source #

Methods

roam :: ((a -> b) -> s -> t) -> p i a b -> p i s t Source #

iroam :: ((i -> a -> b) -> s -> t) -> p j a b -> p (i -> j) s t Source #

Instances
Mapping IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

roam :: ((a -> b) -> s -> t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

iroam :: ((i -> a -> b) -> s -> t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Mapping FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

roam :: ((a -> b) -> s -> t) -> FunArrow i a b -> FunArrow i s t Source #

iroam :: ((i -> a -> b) -> s -> t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

class Visiting p => Traversing p where Source #

Methods

wander :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> p i a b -> p i s t Source #

iwander :: (forall f. Applicative f => (i -> a -> f b) -> s -> f t) -> p j a b -> p (i -> j) s t Source #

Instances
Traversing IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Traversing FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> FunArrow i a b -> FunArrow i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

Monoid r => Traversing (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> IxForget r i a b -> IxForget r i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> IxForget r j a b -> IxForget r (i -> j) s t Source #

Applicative f => Traversing (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f0 :: Type -> Type). Applicative f0 => (a -> f0 b) -> s -> f0 t) -> IxStar f i a b -> IxStar f i s t Source #

iwander :: (forall (f0 :: Type -> Type). Applicative f0 => (i -> a -> f0 b) -> s -> f0 t) -> IxStar f j a b -> IxStar f (i -> j) s t Source #

Monoid r => Traversing (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> Forget r i a b -> Forget r i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> Forget r j a b -> Forget r (i -> j) s t Source #

Applicative f => Traversing (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f0 :: Type -> Type). Applicative f0 => (a -> f0 b) -> s -> f0 t) -> Star f i a b -> Star f i s t Source #

iwander :: (forall (f0 :: Type -> Type). Applicative f0 => (i -> a -> f0 b) -> s -> f0 t) -> Star f j a b -> Star f (i -> j) s t Source #

Concrete profunctors

newtype Star f i a b Source #

Needed for traversals.

Constructors

Star 

Fields

Instances
Applicative f => Traversing (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f0 :: Type -> Type). Applicative f0 => (a -> f0 b) -> s -> f0 t) -> Star f i a b -> Star f i s t Source #

iwander :: (forall (f0 :: Type -> Type). Applicative f0 => (i -> a -> f0 b) -> s -> f0 t) -> Star f j a b -> Star f (i -> j) s t Source #

Applicative f => Visiting (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> Star f i a b -> Star f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> Star f j a b -> Star f (i -> j) s t Source #

Applicative f => Choice (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: Star f i a b -> Star f i (Either a c) (Either b c) Source #

right' :: Star f i a b -> Star f i (Either c a) (Either c b) Source #

Functor f => Strong (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: Star f i a b -> Star f i (a, c) (b, c) Source #

second' :: Star f i a b -> Star f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> Star f i a b -> Star f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> Star f j a b -> Star f (i -> j) s t Source #

Functor f => Profunctor (Star f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Star f i b c -> Star f i a d Source #

lmap :: (a -> b) -> Star f i b c -> Star f i a c Source #

rmap :: (c -> d) -> Star f i b c -> Star f i b d Source #

lcoerce' :: Coercible a b => Star f i a c -> Star f i b c Source #

rcoerce' :: Coercible a b => Star f i c a -> Star f i c b Source #

conjoined__ :: (Star f i a b -> Star f i s t) -> (Star f i a b -> Star f j s t) -> Star f i a b -> Star f j s t Source #

ixcontramap :: (j -> i) -> Star f i a b -> Star f j a b Source #

reStar :: Star f i a b -> Star f j a b Source #

Repack Star to change its index type.

newtype Forget r i a b Source #

Needed for getters and folds.

Constructors

Forget 

Fields

Instances
Monoid r => Traversing (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> Forget r i a b -> Forget r i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> Forget r j a b -> Forget r (i -> j) s t Source #

Monoid r => Visiting (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> Forget r i a b -> Forget r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> Forget r j a b -> Forget r (i -> j) s t Source #

Cochoice (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: Forget r i (Either a d) (Either b d) -> Forget r i a b Source #

unright :: Forget r i (Either d a) (Either d b) -> Forget r i a b Source #

Monoid r => Choice (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Strong (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> Forget r i a b -> Forget r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> Forget r j a b -> Forget r (i -> j) s t Source #

Profunctor (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Forget r i b c -> Forget r i a d Source #

lmap :: (a -> b) -> Forget r i b c -> Forget r i a c Source #

rmap :: (c -> d) -> Forget r i b c -> Forget r i b d Source #

lcoerce' :: Coercible a b => Forget r i a c -> Forget r i b c Source #

rcoerce' :: Coercible a b => Forget r i c a -> Forget r i c b Source #

conjoined__ :: (Forget r i a b -> Forget r i s t) -> (Forget r i a b -> Forget r j s t) -> Forget r i a b -> Forget r j s t Source #

ixcontramap :: (j -> i) -> Forget r i a b -> Forget r j a b Source #

reForget :: Forget r i a b -> Forget r j a b Source #

Repack Forget to change its index type.

newtype ForgetM r i a b Source #

Needed for affine folds.

Constructors

ForgetM 

Fields

Instances
Visiting (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> ForgetM r i a b -> ForgetM r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> ForgetM r j a b -> ForgetM r (i -> j) s t Source #

Cochoice (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: ForgetM r i (Either a d) (Either b d) -> ForgetM r i a b Source #

unright :: ForgetM r i (Either d a) (Either d b) -> ForgetM r i a b Source #

Choice (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: ForgetM r i a b -> ForgetM r i (Either a c) (Either b c) Source #

right' :: ForgetM r i a b -> ForgetM r i (Either c a) (Either c b) Source #

Strong (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: ForgetM r i a b -> ForgetM r i (a, c) (b, c) Source #

second' :: ForgetM r i a b -> ForgetM r i (c, a) (c, b) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> ForgetM r i a b -> ForgetM r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> ForgetM r j a b -> ForgetM r (i -> j) s t Source #

Profunctor (ForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> ForgetM r i b c -> ForgetM r i a d Source #

lmap :: (a -> b) -> ForgetM r i b c -> ForgetM r i a c Source #

rmap :: (c -> d) -> ForgetM r i b c -> ForgetM r i b d Source #

lcoerce' :: Coercible a b => ForgetM r i a c -> ForgetM r i b c Source #

rcoerce' :: Coercible a b => ForgetM r i c a -> ForgetM r i c b Source #

conjoined__ :: (ForgetM r i a b -> ForgetM r i s t) -> (ForgetM r i a b -> ForgetM r j s t) -> ForgetM r i a b -> ForgetM r j s t Source #

ixcontramap :: (j -> i) -> ForgetM r i a b -> ForgetM r j a b Source #

newtype FunArrow i a b Source #

Needed for setters.

Constructors

FunArrow 

Fields

Instances
Mapping FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

roam :: ((a -> b) -> s -> t) -> FunArrow i a b -> FunArrow i s t Source #

iroam :: ((i -> a -> b) -> s -> t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

Traversing FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> FunArrow i a b -> FunArrow i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

Visiting FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t) -> FunArrow i a b -> FunArrow i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

Choice FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Strong FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> FunArrow i a b -> FunArrow i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> FunArrow j a b -> FunArrow (i -> j) s t Source #

Profunctor FunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> FunArrow i b c -> FunArrow i a d Source #

lmap :: (a -> b) -> FunArrow i b c -> FunArrow i a c Source #

rmap :: (c -> d) -> FunArrow i b c -> FunArrow i b d Source #

lcoerce' :: Coercible a b => FunArrow i a c -> FunArrow i b c Source #

rcoerce' :: Coercible a b => FunArrow i c a -> FunArrow i c b Source #

conjoined__ :: (FunArrow i a b -> FunArrow i s t) -> (FunArrow i a b -> FunArrow j s t) -> FunArrow i a b -> FunArrow j s t Source #

ixcontramap :: (j -> i) -> FunArrow i a b -> FunArrow j a b Source #

reFunArrow :: FunArrow i a b -> FunArrow j a b Source #

Repack FunArrow to change its index type.

newtype IxStar f i a b Source #

Needed for indexed traversals.

Constructors

IxStar 

Fields

Instances
Applicative f => Traversing (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f0 :: Type -> Type). Applicative f0 => (a -> f0 b) -> s -> f0 t) -> IxStar f i a b -> IxStar f i s t Source #

iwander :: (forall (f0 :: Type -> Type). Applicative f0 => (i -> a -> f0 b) -> s -> f0 t) -> IxStar f j a b -> IxStar f (i -> j) s t Source #

Applicative f => Visiting (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> IxStar f i a b -> IxStar f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> IxStar f j a b -> IxStar f (i -> j) s t Source #

Applicative f => Choice (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxStar f i a b -> IxStar f i (Either a c) (Either b c) Source #

right' :: IxStar f i a b -> IxStar f i (Either c a) (Either c b) Source #

Functor f => Strong (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxStar f i a b -> IxStar f i (a, c) (b, c) Source #

second' :: IxStar f i a b -> IxStar f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> IxStar f i a b -> IxStar f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> IxStar f j a b -> IxStar f (i -> j) s t Source #

Functor f => Profunctor (IxStar f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxStar f i b c -> IxStar f i a d Source #

lmap :: (a -> b) -> IxStar f i b c -> IxStar f i a c Source #

rmap :: (c -> d) -> IxStar f i b c -> IxStar f i b d Source #

lcoerce' :: Coercible a b => IxStar f i a c -> IxStar f i b c Source #

rcoerce' :: Coercible a b => IxStar f i c a -> IxStar f i c b Source #

conjoined__ :: (IxStar f i a b -> IxStar f i s t) -> (IxStar f i a b -> IxStar f j s t) -> IxStar f i a b -> IxStar f j s t Source #

ixcontramap :: (j -> i) -> IxStar f i a b -> IxStar f j a b Source #

newtype IxForget r i a b Source #

Needed for indexed folds.

Constructors

IxForget 

Fields

Instances
Monoid r => Traversing (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> IxForget r i a b -> IxForget r i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> IxForget r j a b -> IxForget r (i -> j) s t Source #

Monoid r => Visiting (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> IxForget r i a b -> IxForget r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> IxForget r j a b -> IxForget r (i -> j) s t Source #

Cochoice (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: IxForget r i (Either a d) (Either b d) -> IxForget r i a b Source #

unright :: IxForget r i (Either d a) (Either d b) -> IxForget r i a b Source #

Monoid r => Choice (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxForget r i a b -> IxForget r i (Either a c) (Either b c) Source #

right' :: IxForget r i a b -> IxForget r i (Either c a) (Either c b) Source #

Strong (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxForget r i a b -> IxForget r i (a, c) (b, c) Source #

second' :: IxForget r i a b -> IxForget r i (c, a) (c, b) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> IxForget r i a b -> IxForget r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> IxForget r j a b -> IxForget r (i -> j) s t Source #

Profunctor (IxForget r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxForget r i b c -> IxForget r i a d Source #

lmap :: (a -> b) -> IxForget r i b c -> IxForget r i a c Source #

rmap :: (c -> d) -> IxForget r i b c -> IxForget r i b d Source #

lcoerce' :: Coercible a b => IxForget r i a c -> IxForget r i b c Source #

rcoerce' :: Coercible a b => IxForget r i c a -> IxForget r i c b Source #

conjoined__ :: (IxForget r i a b -> IxForget r i s t) -> (IxForget r i a b -> IxForget r j s t) -> IxForget r i a b -> IxForget r j s t Source #

ixcontramap :: (j -> i) -> IxForget r i a b -> IxForget r j a b Source #

newtype IxForgetM r i a b Source #

Needed for indexed affine folds.

Constructors

IxForgetM 

Fields

Instances
Visiting (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (a -> f b) -> s -> f t) -> IxForgetM r i a b -> IxForgetM r i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r0. r0 -> f r0) -> (i -> a -> f b) -> s -> f t) -> IxForgetM r j a b -> IxForgetM r (i -> j) s t Source #

Cochoice (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unleft :: IxForgetM r i (Either a d) (Either b d) -> IxForgetM r i a b Source #

unright :: IxForgetM r i (Either d a) (Either d b) -> IxForgetM r i a b Source #

Choice (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxForgetM r i a b -> IxForgetM r i (Either a c) (Either b c) Source #

right' :: IxForgetM r i a b -> IxForgetM r i (Either c a) (Either c b) Source #

Strong (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxForgetM r i a b -> IxForgetM r i (a, c) (b, c) Source #

second' :: IxForgetM r i a b -> IxForgetM r i (c, a) (c, b) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> IxForgetM r i a b -> IxForgetM r i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> IxForgetM r j a b -> IxForgetM r (i -> j) s t Source #

Profunctor (IxForgetM r) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxForgetM r i b c -> IxForgetM r i a d Source #

lmap :: (a -> b) -> IxForgetM r i b c -> IxForgetM r i a c Source #

rmap :: (c -> d) -> IxForgetM r i b c -> IxForgetM r i b d Source #

lcoerce' :: Coercible a b => IxForgetM r i a c -> IxForgetM r i b c Source #

rcoerce' :: Coercible a b => IxForgetM r i c a -> IxForgetM r i c b Source #

conjoined__ :: (IxForgetM r i a b -> IxForgetM r i s t) -> (IxForgetM r i a b -> IxForgetM r j s t) -> IxForgetM r i a b -> IxForgetM r j s t Source #

ixcontramap :: (j -> i) -> IxForgetM r i a b -> IxForgetM r j a b Source #

newtype IxFunArrow i a b Source #

Needed for indexed setters.

Constructors

IxFunArrow 

Fields

Instances
Mapping IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

roam :: ((a -> b) -> s -> t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

iroam :: ((i -> a -> b) -> s -> t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Traversing IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

iwander :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Visiting IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Choice IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Strong IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

linear :: (forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t) -> IxFunArrow i a b -> IxFunArrow i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t) -> IxFunArrow j a b -> IxFunArrow (i -> j) s t Source #

Profunctor IxFunArrow Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxFunArrow i b c -> IxFunArrow i a d Source #

lmap :: (a -> b) -> IxFunArrow i b c -> IxFunArrow i a c Source #

rmap :: (c -> d) -> IxFunArrow i b c -> IxFunArrow i b d Source #

lcoerce' :: Coercible a b => IxFunArrow i a c -> IxFunArrow i b c Source #

rcoerce' :: Coercible a b => IxFunArrow i c a -> IxFunArrow i c b Source #

conjoined__ :: (IxFunArrow i a b -> IxFunArrow i s t) -> (IxFunArrow i a b -> IxFunArrow j s t) -> IxFunArrow i a b -> IxFunArrow j s t Source #

ixcontramap :: (j -> i) -> IxFunArrow i a b -> IxFunArrow j a b Source #

data StarA f i a b Source #

Needed for conversion of affine traversal back to its VL representation.

Constructors

StarA (forall r. r -> f r) (a -> f b) 
Instances
Functor f => Visiting (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> StarA f i a b -> StarA f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> StarA f j a b -> StarA f (i -> j) s t Source #

Functor f => Choice (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: StarA f i a b -> StarA f i (Either a c) (Either b c) Source #

right' :: StarA f i a b -> StarA f i (Either c a) (Either c b) Source #

Functor f => Strong (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: StarA f i a b -> StarA f i (a, c) (b, c) Source #

second' :: StarA f i a b -> StarA f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> StarA f i a b -> StarA f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> StarA f j a b -> StarA f (i -> j) s t Source #

Functor f => Profunctor (StarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> StarA f i b c -> StarA f i a d Source #

lmap :: (a -> b) -> StarA f i b c -> StarA f i a c Source #

rmap :: (c -> d) -> StarA f i b c -> StarA f i b d Source #

lcoerce' :: Coercible a b => StarA f i a c -> StarA f i b c Source #

rcoerce' :: Coercible a b => StarA f i c a -> StarA f i c b Source #

conjoined__ :: (StarA f i a b -> StarA f i s t) -> (StarA f i a b -> StarA f j s t) -> StarA f i a b -> StarA f j s t Source #

ixcontramap :: (j -> i) -> StarA f i a b -> StarA f j a b Source #

runStarA :: StarA f i a b -> a -> f b Source #

Unwrap StarA.

data IxStarA f i a b Source #

Needed for conversion of indexed affine traversal back to its VL representation.

Constructors

IxStarA (forall r. r -> f r) (i -> a -> f b) 
Instances
Functor f => Visiting (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (a -> f0 b) -> s -> f0 t) -> IxStarA f i a b -> IxStarA f i s t Source #

ivisit :: (forall (f0 :: Type -> Type). Functor f0 => (forall r. r -> f0 r) -> (i -> a -> f0 b) -> s -> f0 t) -> IxStarA f j a b -> IxStarA f (i -> j) s t Source #

Functor f => Choice (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: IxStarA f i a b -> IxStarA f i (Either a c) (Either b c) Source #

right' :: IxStarA f i a b -> IxStarA f i (Either c a) (Either c b) Source #

Functor f => Strong (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: IxStarA f i a b -> IxStarA f i (a, c) (b, c) Source #

second' :: IxStarA f i a b -> IxStarA f i (c, a) (c, b) Source #

linear :: (forall (f0 :: Type -> Type). Functor f0 => (a -> f0 b) -> s -> f0 t) -> IxStarA f i a b -> IxStarA f i s t Source #

ilinear :: (forall (f0 :: Type -> Type). Functor f0 => (i -> a -> f0 b) -> s -> f0 t) -> IxStarA f j a b -> IxStarA f (i -> j) s t Source #

Functor f => Profunctor (IxStarA f) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> IxStarA f i b c -> IxStarA f i a d Source #

lmap :: (a -> b) -> IxStarA f i b c -> IxStarA f i a c Source #

rmap :: (c -> d) -> IxStarA f i b c -> IxStarA f i b d Source #

lcoerce' :: Coercible a b => IxStarA f i a c -> IxStarA f i b c Source #

rcoerce' :: Coercible a b => IxStarA f i c a -> IxStarA f i c b Source #

conjoined__ :: (IxStarA f i a b -> IxStarA f i s t) -> (IxStarA f i a b -> IxStarA f j s t) -> IxStarA f i a b -> IxStarA f j s t Source #

ixcontramap :: (j -> i) -> IxStarA f i a b -> IxStarA f j a b Source #

runIxStarA :: IxStarA f i a b -> i -> a -> f b Source #

Unwrap StarA.

data Exchange a b i s t Source #

Constructors

Exchange (s -> a) (b -> t) 
Instances
Profunctor (Exchange a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Exchange a b i b0 c -> Exchange a b i a0 d Source #

lmap :: (a0 -> b0) -> Exchange a b i b0 c -> Exchange a b i a0 c Source #

rmap :: (c -> d) -> Exchange a b i b0 c -> Exchange a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => Exchange a b i a0 c -> Exchange a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => Exchange a b i c a0 -> Exchange a b i c b0 Source #

conjoined__ :: (Exchange a b i a0 b0 -> Exchange a b i s t) -> (Exchange a b i a0 b0 -> Exchange a b j s t) -> Exchange a b i a0 b0 -> Exchange a b j s t Source #

ixcontramap :: (j -> i) -> Exchange a b i a0 b0 -> Exchange a b j a0 b0 Source #

data Store a b i s t Source #

Type to represent the components of a lens.

Constructors

Store (s -> a) (s -> b -> t) 
Instances
Strong (Store a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: Store a b i a0 b0 -> Store a b i (a0, c) (b0, c) Source #

second' :: Store a b i a0 b0 -> Store a b i (c, a0) (c, b0) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a0 -> f b0) -> s -> f t) -> Store a b i a0 b0 -> Store a b i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a0 -> f b0) -> s -> f t) -> Store a b j a0 b0 -> Store a b (i -> j) s t Source #

Profunctor (Store a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Store a b i b0 c -> Store a b i a0 d Source #

lmap :: (a0 -> b0) -> Store a b i b0 c -> Store a b i a0 c Source #

rmap :: (c -> d) -> Store a b i b0 c -> Store a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => Store a b i a0 c -> Store a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => Store a b i c a0 -> Store a b i c b0 Source #

conjoined__ :: (Store a b i a0 b0 -> Store a b i s t) -> (Store a b i a0 b0 -> Store a b j s t) -> Store a b i a0 b0 -> Store a b j s t Source #

ixcontramap :: (j -> i) -> Store a b i a0 b0 -> Store a b j a0 b0 Source #

data Market a b i s t Source #

Type to represent the components of a prism.

Constructors

Market (b -> t) (s -> Either t a) 
Instances
Choice (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: Market a b i a0 b0 -> Market a b i (Either a0 c) (Either b0 c) Source #

right' :: Market a b i a0 b0 -> Market a b i (Either c a0) (Either c b0) Source #

Profunctor (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Market a b i b0 c -> Market a b i a0 d Source #

lmap :: (a0 -> b0) -> Market a b i b0 c -> Market a b i a0 c Source #

rmap :: (c -> d) -> Market a b i b0 c -> Market a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => Market a b i a0 c -> Market a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => Market a b i c a0 -> Market a b i c b0 Source #

conjoined__ :: (Market a b i a0 b0 -> Market a b i s t) -> (Market a b i a0 b0 -> Market a b j s t) -> Market a b i a0 b0 -> Market a b j s t Source #

ixcontramap :: (j -> i) -> Market a b i a0 b0 -> Market a b j a0 b0 Source #

Functor (Market a b i s) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

fmap :: (a0 -> b0) -> Market a b i s a0 -> Market a b i s b0 #

(<$) :: a0 -> Market a b i s b0 -> Market a b i s a0 #

data AffineMarket a b i s t Source #

Type to represent the components of an affine traversal.

Constructors

AffineMarket (s -> b -> t) (s -> Either t a) 
Instances
Visiting (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

visit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a0 -> f b0) -> s -> f t) -> AffineMarket a b i a0 b0 -> AffineMarket a b i s t Source #

ivisit :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a0 -> f b0) -> s -> f t) -> AffineMarket a b j a0 b0 -> AffineMarket a b (i -> j) s t Source #

Choice (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

left' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (Either a0 c) (Either b0 c) Source #

right' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (Either c a0) (Either c b0) Source #

Strong (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

first' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (a0, c) (b0, c) Source #

second' :: AffineMarket a b i a0 b0 -> AffineMarket a b i (c, a0) (c, b0) Source #

linear :: (forall (f :: Type -> Type). Functor f => (a0 -> f b0) -> s -> f t) -> AffineMarket a b i a0 b0 -> AffineMarket a b i s t Source #

ilinear :: (forall (f :: Type -> Type). Functor f => (i -> a0 -> f b0) -> s -> f t) -> AffineMarket a b j a0 b0 -> AffineMarket a b (i -> j) s t Source #

Profunctor (AffineMarket a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a0 -> b0) -> (c -> d) -> AffineMarket a b i b0 c -> AffineMarket a b i a0 d Source #

lmap :: (a0 -> b0) -> AffineMarket a b i b0 c -> AffineMarket a b i a0 c Source #

rmap :: (c -> d) -> AffineMarket a b i b0 c -> AffineMarket a b i b0 d Source #

lcoerce' :: Coercible a0 b0 => AffineMarket a b i a0 c -> AffineMarket a b i b0 c Source #

rcoerce' :: Coercible a0 b0 => AffineMarket a b i c a0 -> AffineMarket a b i c b0 Source #

conjoined__ :: (AffineMarket a b i a0 b0 -> AffineMarket a b i s t) -> (AffineMarket a b i a0 b0 -> AffineMarket a b j s t) -> AffineMarket a b i a0 b0 -> AffineMarket a b j s t Source #

ixcontramap :: (j -> i) -> AffineMarket a b i a0 b0 -> AffineMarket a b j a0 b0 Source #

newtype Tagged i a b Source #

Tag a value with not one but two phantom type parameters (so that Tagged can be used as an indexed profunctor).

Constructors

Tagged 

Fields

Instances
Choice Tagged Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

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

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

Costrong Tagged Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

unfirst :: Tagged i (a, d) (b, d) -> Tagged i a b Source #

unsecond :: Tagged i (d, a) (d, b) -> Tagged i a b Source #

Profunctor Tagged Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged i b c -> Tagged i a d Source #

lmap :: (a -> b) -> Tagged i b c -> Tagged i a c Source #

rmap :: (c -> d) -> Tagged i b c -> Tagged i b d Source #

lcoerce' :: Coercible a b => Tagged i a c -> Tagged i b c Source #

rcoerce' :: Coercible a b => Tagged i c a -> Tagged i c b Source #

conjoined__ :: (Tagged i a b -> Tagged i s t) -> (Tagged i a b -> Tagged j s t) -> Tagged i a b -> Tagged j s t Source #

ixcontramap :: (j -> i) -> Tagged i a b -> Tagged j a b Source #

Functor (Tagged i a) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

fmap :: (a0 -> b) -> Tagged i a a0 -> Tagged i a b #

(<$) :: a0 -> Tagged i a b -> Tagged i a a0 #

data Context a b t Source #

Constructors

Context (b -> t) a 
Instances
Functor (Context a b) Source # 
Instance details

Defined in Data.Profunctor.Indexed

Methods

fmap :: (a0 -> b0) -> Context a b a0 -> Context a b b0 #

(<$) :: a0 -> Context a b b0 -> Context a b a0 #

Utilities

(#.) :: Coercible b c => (b -> c) -> (a -> b) -> a -> c infixr 9 Source #

Composition operator where the first argument must be an identity function up to representational equivalence (e.g. a newtype wrapper or unwrapper), and will be ignored at runtime.

(.#) :: Coercible a b => (b -> c) -> (a -> b) -> a -> c infixl 8 Source #

Composition operator where the second argument must be an identity function up to representational equivalence (e.g. a newtype wrapper or unwrapper), and will be ignored at runtime.