cartesian-profunctors
Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Cocartesian.Free

Synopsis

The free Cocartesian profunctors

data FreeCocartesian (p :: Type -> Type -> Type) a b Source #

Free Cocartesian profunctor is FreeMonoidal profunctor with respect to Either.

Caution about Cartesian instance

Note that FreeCocartesian p have an instance of Cartesian, by distributing product on sums to sum of products of individual profunctors. When it is desirable to disable Cartesian instance of FreeCocartesian p, use ForgetCartesian to ignore Cartesian instance of p.

Because there are some profunctors which are both Cartesian and Cocartesian but do not satisfy distributive laws, using FreeCocartesian with such profunctors might cause a surprising behavior.

For example, Joker [] is not distributive, as Alternative [] is not distributive as shown below.

>>> import Control.Applicative
>>> let x = [id, id]
>>> let y = [1]; z = [2]
>>> x <*> (y <|> z)
[1,2,1,2]
>>> (x <*> y) <|> (x <*> z)
[1,1,2,2]

With such non-distributive Cartesian p, foldFreeCocartesian does not preserve the Cartesian operations. The following equation does not have to hold.

-- Not necessarily holds!
foldFreeCocartesian id (ps *** qs)
 == foldFreeCocartesian id ps *** foldFreeCocartesian id qs

Constructors

Neutral (a -> Void) 
Cons (Day Either p (FreeCocartesian p) a b) 

Instances

Instances details
ProfunctorMonad FreeCocartesian Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

proreturn :: forall (p :: Type -> Type -> Type). Profunctor p => p :-> FreeCocartesian p #

projoin :: forall (p :: Type -> Type -> Type). Profunctor p => FreeCocartesian (FreeCocartesian p) :-> FreeCocartesian p #

ProfunctorFunctor FreeCocartesian Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

promap :: forall (p :: Type -> Type -> Type) (q :: Type -> Type -> Type). Profunctor p => (p :-> q) -> FreeCocartesian p :-> FreeCocartesian q #

Cartesian p => Cartesian (FreeCocartesian p) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

proUnit :: FreeCocartesian p a () Source #

proProduct :: (a -> (a1, a2)) -> ((b1, b2) -> b) -> FreeCocartesian p a1 b1 -> FreeCocartesian p a2 b2 -> FreeCocartesian p a b Source #

(***) :: FreeCocartesian p a b -> FreeCocartesian p a' b' -> FreeCocartesian p (a, a') (b, b') Source #

(&&&) :: FreeCocartesian p a b -> FreeCocartesian p a b' -> FreeCocartesian p a (b, b') Source #

proPower :: forall (n :: Nat) a b. KnownNat n => FreeCocartesian p a b -> FreeCocartesian p (Finite n -> a) (Finite n -> b) Source #

Profunctor p => Cocartesian (FreeCocartesian p) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

proEmpty :: FreeCocartesian p Void b Source #

proSum :: (a -> Either a1 a2) -> (Either b1 b2 -> b) -> FreeCocartesian p a1 b1 -> FreeCocartesian p a2 b2 -> FreeCocartesian p a b Source #

(+++) :: FreeCocartesian p a b -> FreeCocartesian p a' b' -> FreeCocartesian p (Either a a') (Either b b') Source #

(|||) :: FreeCocartesian p a b -> FreeCocartesian p a' b -> FreeCocartesian p (Either a a') b Source #

proTimes :: forall (n :: Nat) a b. KnownNat n => FreeCocartesian p a b -> FreeCocartesian p (Finite n, a) (Finite n, b) Source #

Profunctor (FreeCocartesian p) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

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

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

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

(#.) :: forall a b c q. Coercible c b => q b c -> FreeCocartesian p a b -> FreeCocartesian p a c #

(.#) :: forall a b c q. Coercible b a => FreeCocartesian p b c -> q a b -> FreeCocartesian p a c #

Cartesian p => Applicative (FreeCocartesian p a) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

pure :: a0 -> FreeCocartesian p a a0 #

(<*>) :: FreeCocartesian p a (a0 -> b) -> FreeCocartesian p a a0 -> FreeCocartesian p a b #

liftA2 :: (a0 -> b -> c) -> FreeCocartesian p a a0 -> FreeCocartesian p a b -> FreeCocartesian p a c #

(*>) :: FreeCocartesian p a a0 -> FreeCocartesian p a b -> FreeCocartesian p a b #

(<*) :: FreeCocartesian p a a0 -> FreeCocartesian p a b -> FreeCocartesian p a a0 #

Functor (FreeCocartesian p a) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

fmap :: (a0 -> b) -> FreeCocartesian p a a0 -> FreeCocartesian p a b #

(<$) :: a0 -> FreeCocartesian p a b -> FreeCocartesian p a a0 #

liftF :: p a b -> FreeCocartesian p a b Source #

foldFree :: forall (q :: Type -> Type -> Type) (p :: Type -> Type -> Type). Cocartesian q => (p :-> q) -> FreeCocartesian p :-> q Source #

emptyF :: forall (p :: Type -> Type -> Type) b. FreeCocartesian p Void b Source #

sumF :: forall (p :: Type -> Type -> Type) a b a' b'. FreeCocartesian p a b -> FreeCocartesian p a' b' -> FreeCocartesian p (Either a a') (Either b b') Source #

Distributive Cartesian on FreeCocartesian p

multF :: forall (p :: Type -> Type -> Type) (q :: Type -> Type -> Type) (r :: Type -> Type -> Type) a b a' b'. ProductOp p q r -> FreeCocartesian p a b -> FreeCocartesian q a' b' -> FreeCocartesian r (a, a') (b, b') Source #

Newtype wrapper

newtype ForgetCocartesian (p :: Type -> Type -> Type) a b Source #

Forgets Cocartesian instance from a Profunctor.

Constructors

ForgetCocartesian 

Fields

Instances

Instances details
Cartesian p => Cartesian (ForgetCocartesian p) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

proUnit :: ForgetCocartesian p a () Source #

proProduct :: (a -> (a1, a2)) -> ((b1, b2) -> b) -> ForgetCocartesian p a1 b1 -> ForgetCocartesian p a2 b2 -> ForgetCocartesian p a b Source #

(***) :: ForgetCocartesian p a b -> ForgetCocartesian p a' b' -> ForgetCocartesian p (a, a') (b, b') Source #

(&&&) :: ForgetCocartesian p a b -> ForgetCocartesian p a b' -> ForgetCocartesian p a (b, b') Source #

proPower :: forall (n :: Nat) a b. KnownNat n => ForgetCocartesian p a b -> ForgetCocartesian p (Finite n -> a) (Finite n -> b) Source #

Profunctor p => Profunctor (ForgetCocartesian p) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

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

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

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

(#.) :: forall a b c q. Coercible c b => q b c -> ForgetCocartesian p a b -> ForgetCocartesian p a c #

(.#) :: forall a b c q. Coercible b a => ForgetCocartesian p b c -> q a b -> ForgetCocartesian p a c #

Functor (p a) => Functor (ForgetCocartesian p a) Source # 
Instance details

Defined in Data.Profunctor.Cocartesian.Free

Methods

fmap :: (a0 -> b) -> ForgetCocartesian p a a0 -> ForgetCocartesian p a b #

(<$) :: a0 -> ForgetCocartesian p a b -> ForgetCocartesian p a a0 #

Utility functions handling product (,) and coproduct Either of

assocEither :: Either (Either a b) c -> Either a (Either b c) Source #

distL :: (a, Either b1 b2) -> Either (a, b1) (a, b2) Source #

undistL :: Either (a, b1) (a, b2) -> (a, Either b1 b2) Source #

distR :: (Either a1 a2, b) -> Either (a1, b) (a2, b) Source #

undistR :: Either (a1, b) (a2, b) -> (Either a1 a2, b) Source #