profunctor-arrows-0.0.0.2: Profunctor arrows

Safe HaskellSafe
LanguageHaskell2010

Data.Profunctor.Arrow.Free

Synopsis

Documentation

newtype PArrow p a b Source #

Lift a profunctor into an Arrow cofreely.

Constructors

PArrow 

Fields

  • runPArrow :: forall x y. p (b, x) y -> p (a, x) y
     
Instances
Profunctor p => Strong (PArrow p) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

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

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

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

Defined in Data.Profunctor.Arrow.Free

Methods

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

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

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

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

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

Profunctor p => Category (PArrow p :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

id :: PArrow p a a #

(.) :: PArrow p b c -> PArrow p a b -> PArrow p a c #

toArrow :: Arrow a => PArrow a b c -> a b c Source #

fromArrow :: Arrow a => a b c -> PArrow a b c Source #

data Free p a b where Source #

Free monoid in the category of profunctors.

See https://arxiv.org/abs/1406.4823 section 6.2.

Constructors

Parr :: (a -> b) -> Free p a b 
Free :: p x b -> Free p a x -> Free p a b 
Instances
Mapping p => Mapping (Free p) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

map' :: Functor f => Free p a b -> Free p (f a) (f b) #

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

Traversing p => Traversing (Free p) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

traverse' :: Traversable f => Free p a b -> Free p (f a) (f b) #

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

Choice p => Choice (Free p) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

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

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

Closed p => Closed (Free p) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

closed :: Free p a b -> Free p (x -> a) (x -> b) #

Strong p => Strong (Free p) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

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

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

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

Defined in Data.Profunctor.Arrow.Free

Methods

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

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

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

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

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

Profunctor p => Category (Free p :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

id :: Free p a a #

(.) :: Free p b c -> Free p a b -> Free p a c #

foldFree :: Category q => Profunctor q => (p :-> q) -> Free p a b -> q a b Source #

Given a natural transformation this returns a profunctor.

hoistFree :: (p :-> q) -> Free p a b -> Free q a b Source #

Lift a natural transformation from f to g into a natural transformation from Free f to Free g.

newtype Append r a b Source #

Constructors

Append 

Fields

Instances
Profunctor (Append r) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

dimap :: (a -> b) -> (c -> d) -> Append r b c -> Append r a d #

lmap :: (a -> b) -> Append r b c -> Append r a c #

rmap :: (b -> c) -> Append r a b -> Append r a c #

(#.) :: Coercible c b => q b c -> Append r a b -> Append r a c #

(.#) :: Coercible b a => Append r b c -> q a b -> Append r a c #

Monoid r => Category (Append r :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Arrow.Free

Methods

id :: Append r a a #

(.) :: Append r b c -> Append r a b -> Append r a c #