hs-functors-0.1.2.0: Functors from products of Haskell and its dual to Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor

Documentation

class Profunctor p where Source #

Methods

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

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

rmap :: (b -> c) -> p a b -> p a c Source #

Instances

Functor f => Profunctor (Kleisli f) Source # 

Methods

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

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

rmap :: (b -> c) -> Kleisli f a b -> Kleisli f a c Source #

Profunctor ((->) LiftedRep LiftedRep) Source # 

Methods

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

lmap :: (a -> b) -> (LiftedRep -> LiftedRep) b c -> (LiftedRep -> LiftedRep) a c Source #

rmap :: (b -> c) -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a c Source #

Functor f => Profunctor (Cokleisli * f) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Cokleisli * f b c -> Cokleisli * f a d Source #

lmap :: (a -> b) -> Cokleisli * f b c -> Cokleisli * f a c Source #

rmap :: (b -> c) -> Cokleisli * f a b -> Cokleisli * f a c Source #

(^>>) :: Profunctor p => (a -> b) -> p b c -> p a c infixr 1 Source #

(>>^) :: Profunctor p => p a b -> (b -> c) -> p a c infixr 1 Source #

(<<^) :: Profunctor p => p b c -> (a -> b) -> p a c infixr 1 Source #

(^<<) :: Profunctor p => (b -> c) -> p a b -> p a c infixr 1 Source #

class Profunctor p => Strong f p where Source #

Minimal complete definition

strong

Methods

strong :: p a₁ b₁ -> p a₂ b₂ -> p (f a₁ a₂) (f b₁ b₂) Source #

Instances

Functor f => Strong Either (Kleisli f) Source # 

Methods

strong :: Kleisli f a₁ b₁ -> Kleisli f a₂ b₂ -> Kleisli f (Either a₁ a₂) (Either b₁ b₂) Source #

Applicative p => Strong (,) (Kleisli p) Source # 

Methods

strong :: Kleisli p a₁ b₁ -> Kleisli p a₂ b₂ -> Kleisli p (a₁, a₂) (b₁, b₂) Source #

Strong Either ((->) LiftedRep LiftedRep) Source # 

Methods

strong :: (LiftedRep -> LiftedRep) a₁ b₁ -> (LiftedRep -> LiftedRep) a₂ b₂ -> (LiftedRep -> LiftedRep) (Either a₁ a₂) (Either b₁ b₂) Source #

Comonad ɯ => Strong Either (Cokleisli * ɯ) Source # 

Methods

strong :: Cokleisli * ɯ a₁ b₁ -> Cokleisli * ɯ a₂ b₂ -> Cokleisli * ɯ (Either a₁ a₂) (Either b₁ b₂) Source #

Strong (,) ((->) LiftedRep LiftedRep) Source # 

Methods

strong :: (LiftedRep -> LiftedRep) a₁ b₁ -> (LiftedRep -> LiftedRep) a₂ b₂ -> (LiftedRep -> LiftedRep) (a₁, a₂) (b₁, b₂) Source #

(***) :: Strong (,) p => p a₁ b₁ -> p a₂ b₂ -> p (a₁, a₂) (b₁, b₂) infixr 3 Source #

(&&&) :: Strong (,) p => p a b₁ -> p a b₂ -> p a (b₁, b₂) infixr 3 Source #

(+++) :: Strong Either p => p a₁ b₁ -> p a₂ b₂ -> p (Either a₁ a₂) (Either b₁ b₂) infixr 2 Source #

(|||) :: Strong Either p => p a₁ b -> p a₂ b -> p (Either a₁ a₂) b infixr 2 Source #

class Profunctor p => Costrong f p where Source #

Methods

costrongL :: p (f a c) (f b c) -> p a b Source #

costrongR :: p (f a b) (f a c) -> p b c Source #

costrongL :: Braided f => p (f a c) (f b c) -> p a b Source #

costrongR :: Braided f => p (f a b) (f a c) -> p b c Source #

Instances

Monad m => Costrong Either (Kleisli m) Source # 

Methods

costrongL :: Kleisli m (Either a c) (Either b c) -> Kleisli m a b Source #

costrongR :: Kleisli m (Either a b) (Either a c) -> Kleisli m b c Source #

MonadFix m => Costrong (,) (Kleisli m) Source # 

Methods

costrongL :: Kleisli m (a, c) (b, c) -> Kleisli m a b Source #

costrongR :: Kleisli m (a, b) (a, c) -> Kleisli m b c Source #

Costrong Either ((->) LiftedRep LiftedRep) Source # 

Methods

costrongL :: (LiftedRep -> LiftedRep) (Either a c) (Either b c) -> (LiftedRep -> LiftedRep) a b Source #

costrongR :: (LiftedRep -> LiftedRep) (Either a b) (Either a c) -> (LiftedRep -> LiftedRep) b c Source #

Functor f => Costrong Either (Cokleisli * f) Source # 

Methods

costrongL :: Cokleisli * f (Either a c) (Either b c) -> Cokleisli * f a b Source #

costrongR :: Cokleisli * f (Either a b) (Either a c) -> Cokleisli * f b c Source #

Costrong (,) ((->) LiftedRep LiftedRep) Source # 

Methods

costrongL :: (LiftedRep -> LiftedRep) (a, c) (b, c) -> (LiftedRep -> LiftedRep) a b Source #

costrongR :: (LiftedRep -> LiftedRep) (a, b) (a, c) -> (LiftedRep -> LiftedRep) b c Source #

class Profunctor p => Closed f p where Source #

Minimal complete definition

closed

Methods

closed :: p a b -> p (f a) (f b) Source #

Instances

(Traversable f, Applicative p) => Closed f (Kleisli p) Source # 

Methods

closed :: Kleisli p a b -> Kleisli p (f a) (f b) Source #

(Cotraversable f, Functor ɯ) => Closed f (Cokleisli * ɯ) Source # 

Methods

closed :: Cokleisli * ɯ a b -> Cokleisli * ɯ (f a) (f b) Source #

Functor f => Closed f ((->) LiftedRep LiftedRep) Source # 

Methods

closed :: (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) (f a) (f b) Source #