proarrow
Safe HaskellNone
LanguageGHC2024

Proarrow.Category.Instance.Free

Documentation

type family All (cs :: [Kind -> Constraint]) k where ... Source Comments #

Equations

All ('[] :: [Kind -> Constraint]) k = () 
All (c ': cs) k = (c k, All cs k) 

class (All cs k => c k) => FromAll (cs :: [Kind -> Constraint]) (c :: Kind -> Constraint) k Source Comments #

Instances

Instances details
(All cs k => c k) => FromAll cs c k Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

class (forall k. FromAll cs c k) => Elem (c :: Kind -> Constraint) (cs :: [Kind -> Constraint]) Source Comments #

Instances

Instances details
Elem c (c ': cs) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Elem c cs => Elem c (d ': cs) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

newtype FREE (cs :: [Kind -> Constraint]) (p :: CAT j) Source Comments #

Constructors

EMB j 

Instances

Instances details
Elem Monoidal cs => IsFreeOb (UnitF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (UnitF :: FREE cs p)) => r) -> r Source Comments #

Elem HasInitialObject cs => IsFreeOb (InitF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Initial

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (InitF :: FREE cs p)) => r) -> r Source Comments #

Elem HasTerminalObject cs => IsFreeOb (TermF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (TermF :: FREE cs p)) => r) -> r Source Comments #

(Ob a, Ob b, Elem Monoidal cs) => IsFreeOb (a **! b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a **! b)) => r) -> r Source Comments #

(Ob a, Ob b, Elem HasBinaryCoproducts cs) => IsFreeOb (a + b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryCoproduct

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a + b)) => r) -> r Source Comments #

(Ob a, Ob b, Elem HasBinaryProducts cs) => IsFreeOb (a *! b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a *! b)) => r) -> r Source Comments #

(Ob a, Ob b, Elem Closed cs, Elem Monoidal cs) => IsFreeOb (a --> b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Exponential

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a --> b)) => r) -> r Source Comments #

(Ok cs p, Elem Monoidal cs) => Monoidal (FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Associated Types

type Unit 
Instance details

Defined in Proarrow.Category.Monoidal

type Unit = UnitF :: FREE cs p

Methods

withOb2 :: forall (a :: FREE cs p) (b :: FREE cs p) r. (Ob a, Ob b) => (Ob (a ** b) => r) -> r Source Comments #

leftUnitor :: forall (a :: FREE cs p). Ob a => ((Unit :: FREE cs p) ** a) ~> a Source Comments #

leftUnitorInv :: forall (a :: FREE cs p). Ob a => a ~> ((Unit :: FREE cs p) ** a) Source Comments #

rightUnitor :: forall (a :: FREE cs p). Ob a => (a ** (Unit :: FREE cs p)) ~> a Source Comments #

rightUnitorInv :: forall (a :: FREE cs p). Ob a => a ~> (a ** (Unit :: FREE cs p)) Source Comments #

associator :: forall (a :: FREE cs p) (b :: FREE cs p) (c :: FREE cs p). (Ob a, Ob b, Ob c) => ((a ** b) ** c) ~> (a ** (b ** c)) Source Comments #

associatorInv :: forall (a :: FREE cs p) (b :: FREE cs p) (c :: FREE cs p). (Ob a, Ob b, Ob c) => (a ** (b ** c)) ~> ((a ** b) ** c) Source Comments #

Ok cs p => CategoryOf (FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Associated Types

type (~>) 
Instance details

Defined in Proarrow.Category.Instance.Free

type (~>) = Free :: FREE cs p -> FREE cs p -> Type
(Ok cs p, Elem HasBinaryCoproducts cs) => HasBinaryCoproducts (FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryCoproduct

Methods

withObCoprod :: forall (a :: FREE cs p) (b :: FREE cs p) r. (Ob a, Ob b) => (Ob (a || b) => r) -> r Source Comments #

lft :: forall (a :: FREE cs p) (b :: FREE cs p). (Ob a, Ob b) => a ~> (a || b) Source Comments #

rgt :: forall (a :: FREE cs p) (b :: FREE cs p). (Ob a, Ob b) => b ~> (a || b) Source Comments #

(|||) :: forall (x :: FREE cs p) (a :: FREE cs p) (y :: FREE cs p). (x ~> a) -> (y ~> a) -> (x || y) ~> a Source Comments #

(+++) :: forall (a :: FREE cs p) (b :: FREE cs p) (x :: FREE cs p) (y :: FREE cs p). (a ~> x) -> (b ~> y) -> (a || b) ~> (x || y) Source Comments #

(Ok cs p, Elem HasBinaryProducts cs) => HasBinaryProducts (FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

Methods

withObProd :: forall (a :: FREE cs p) (b :: FREE cs p) r. (Ob a, Ob b) => (Ob (a && b) => r) -> r Source Comments #

fst :: forall (a :: FREE cs p) (b :: FREE cs p). (Ob a, Ob b) => (a && b) ~> a Source Comments #

snd :: forall (a :: FREE cs p) (b :: FREE cs p). (Ob a, Ob b) => (a && b) ~> b Source Comments #

(&&&) :: forall (a :: FREE cs p) (x :: FREE cs p) (y :: FREE cs p). (a ~> x) -> (a ~> y) -> a ~> (x && y) Source Comments #

(***) :: forall (a :: FREE cs p) (b :: FREE cs p) (x :: FREE cs p) (y :: FREE cs p). (a ~> x) -> (b ~> y) -> (a && b) ~> (x && y) Source Comments #

(Ok cs p, Elem Closed cs, Elem Monoidal cs) => Closed (FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Exponential

Methods

withObExp :: forall (a :: FREE cs p) (b :: FREE cs p) r. (Ob a, Ob b) => (Ob (a ~~> b) => r) -> r Source Comments #

curry :: forall (a :: FREE cs p) (b :: FREE cs p) (c :: FREE cs p). (Ob a, Ob b) => ((a ** b) ~> c) -> a ~> (b ~~> c) Source Comments #

apply :: forall (a :: FREE cs p) (b :: FREE cs p). (Ob a, Ob b) => ((a ~~> b) ** a) ~> b Source Comments #

(^^^) :: forall (a :: FREE cs p) (b :: FREE cs p) (x :: FREE cs p) (y :: FREE cs p). (b ~> y) -> (x ~> a) -> (a ~~> b) ~> (x ~~> y) Source Comments #

(Ok cs p, Elem HasInitialObject cs) => HasInitialObject (FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Initial

Associated Types

type InitialObject 
Instance details

Defined in Proarrow.Object.Initial

type InitialObject = InitF :: FREE cs p

Methods

initiate :: forall (a :: FREE cs p). Ob a => (InitialObject :: FREE cs p) ~> a Source Comments #

(Ok cs p, Elem HasTerminalObject cs) => HasTerminalObject (FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

Associated Types

type TerminalObject 
Instance details

Defined in Proarrow.Object.Terminal

type TerminalObject = TermF :: FREE cs p

Methods

terminate :: forall (a :: FREE cs p). Ob a => a ~> (TerminalObject :: FREE cs p) Source Comments #

Ok cs p => Promonad (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Methods

id :: forall (a :: FREE cs p). Ob a => Free a a Source Comments #

(.) :: forall (b :: FREE cs p) (c :: FREE cs p) (a :: FREE cs p). Free b c -> Free a b -> Free a c Source Comments #

(Ok cs p, Elem Monoidal cs) => MonoidalProfunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Methods

par0 :: Free (Unit :: FREE cs p) (Unit :: FREE cs p) Source Comments #

par :: forall (x1 :: FREE cs p) (x2 :: FREE cs p) (y1 :: FREE cs p) (y2 :: FREE cs p). Free x1 x2 -> Free y1 y2 -> Free (x1 ** y1) (x2 ** y2) Source Comments #

Ok cs p => Profunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Methods

dimap :: forall (c :: FREE cs p) (a :: FREE cs p) (b :: FREE cs p) (d :: FREE cs p). (c ~> a) -> (b ~> d) -> Free a b -> Free c d Source Comments #

(\\) :: forall (a :: FREE cs p) (b :: FREE cs p) r. ((Ob a, Ob b) => r) -> Free a b -> r Source Comments #

type Lower (f :: j +-> k) (UnitF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

type Lower (f :: j +-> k) (UnitF :: FREE cs p) = Unit :: k
type Lower (f :: j +-> k) (InitF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Initial

type Lower (f :: j +-> k) (InitF :: FREE cs p) = InitialObject :: k
type Lower (f :: j +-> k) (TermF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

type Lower (f :: j +-> k) (TermF :: FREE cs p) = TerminalObject :: k
type Lower (f :: j +-> k) (a **! b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

type Lower (f :: j +-> k) (a **! b :: FREE cs p) = Lower f a ** Lower f b
type Lower (f :: j +-> k) (a + b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryCoproduct

type Lower (f :: j +-> k) (a + b :: FREE cs p) = Lower f a || Lower f b
type Lower (f :: j +-> k) (a *! b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

type Lower (f :: j +-> k) (a *! b :: FREE cs p) = Lower f a && Lower f b
type Lower (f :: j +-> k) (a --> b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Exponential

type Lower (f :: j +-> k) (a --> b :: FREE cs p) = Lower f a ~~> Lower f b
type UN ('EMB :: j -> FREE cs p) ('EMB a :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

type UN ('EMB :: j -> FREE cs p) ('EMB a :: FREE cs p) = a
type Unit Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

type Unit = UnitF :: FREE cs p
type (~>) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

type (~>) = Free :: FREE cs p -> FREE cs p -> Type
type InitialObject Source Comments # 
Instance details

Defined in Proarrow.Object.Initial

type InitialObject = InitF :: FREE cs p
type TerminalObject Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

type TerminalObject = TermF :: FREE cs p
type Ob (a :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

type Ob (a :: FREE cs p) = (IsFreeOb a, Typeable a)
type (a :: FREE cs p) ** (b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

type (a :: FREE cs p) ** (b :: FREE cs p) = a **! b
type (a :: FREE cs p) || (b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryCoproduct

type (a :: FREE cs p) || (b :: FREE cs p) = a + b
type (a :: FREE cs p) && (b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

type (a :: FREE cs p) && (b :: FREE cs p) = a *! b
type (a :: FREE cs p) ~~> (b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Exponential

type (a :: FREE cs p) ~~> (b :: FREE cs p) = a --> b

data Free (a :: FREE cs p) (b :: FREE cs p) where Source Comments #

Constructors

Id :: forall {j} {cs :: [Kind -> Constraint]} {p :: CAT j} (a :: FREE cs p). Ob a => Free a a 
Emb :: forall {j} (a1 :: j) (b1 :: j) (p :: CAT j) (cs :: [Kind -> Constraint]) (a :: FREE cs p). (Ob a1, Ob b1, Typeable a1, Typeable b1) => p a1 b1 -> Free a ('EMB a1 :: FREE cs p) -> Free a ('EMB b1 :: FREE cs p) 
Str :: forall {j} {cs :: [Kind -> Constraint]} {p :: CAT j} (c :: Kind -> Constraint) (a1 :: FREE cs p) (b :: FREE cs p) (a :: FREE cs p). (HasStructure cs p c, Ob a1, Ob b) => Struct c a1 b -> Free a a1 -> Free a b 

Instances

Instances details
Ok cs p => Promonad (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Methods

id :: forall (a :: FREE cs p). Ob a => Free a a Source Comments #

(.) :: forall (b :: FREE cs p) (c :: FREE cs p) (a :: FREE cs p). Free b c -> Free a b -> Free a c Source Comments #

(Ok cs p, Elem Monoidal cs) => MonoidalProfunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Methods

par0 :: Free (Unit :: FREE cs p) (Unit :: FREE cs p) Source Comments #

par :: forall (x1 :: FREE cs p) (x2 :: FREE cs p) (y1 :: FREE cs p) (y2 :: FREE cs p). Free x1 x2 -> Free y1 y2 -> Free (x1 ** y1) (x2 ** y2) Source Comments #

Ok cs p => Profunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Methods

dimap :: forall (c :: FREE cs p) (a :: FREE cs p) (b :: FREE cs p) (d :: FREE cs p). (c ~> a) -> (b ~> d) -> Free a b -> Free c d Source Comments #

(\\) :: forall (a :: FREE cs p) (b :: FREE cs p) r. ((Ob a, Ob b) => r) -> Free a b -> r Source Comments #

WithShow a => Show (Free a b) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Methods

showsPrec :: Int -> Free a b -> ShowS Comments #

show :: Free a b -> String Comments #

showList :: [Free a b] -> ShowS Comments #

WithEq a => Eq (Free a b) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Methods

(==) :: Free a b -> Free a b -> Bool Comments #

(/=) :: Free a b -> Free a b -> Bool Comments #

emb :: forall {j} (a :: j) (b :: j) (cs :: [Kind -> Constraint]) p. (Ob a, Ob b, Typeable a, Typeable b, Ok cs p) => p a b %1 -> Free ('EMB a :: FREE cs p) ('EMB b :: FREE cs p) Source Comments #

class (forall (x :: k) (y :: k1). Eq (p x y)) => Eq2 (p :: k -> k1 -> Type) Source Comments #

Instances

Instances details
(forall (x :: k1) (y :: k2). Eq (p x y)) => Eq2 (p :: k1 -> k2 -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

class (forall (x :: k) (y :: k1). Show (p x y)) => Show2 (p :: k -> k1 -> Type) Source Comments #

Instances

Instances details
(forall (x :: k1) (y :: k2). Show (p x y)) => Show2 (p :: k1 -> k2 -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

class (Typeable p, Typeable cs, Typeable j, All cs (FREE cs p)) => Ok (cs :: [Kind -> Constraint]) (p :: CAT j) Source Comments #

Instances

Instances details
(Typeable p, Typeable cs, Typeable j, All cs (FREE cs p)) => Ok cs (p :: CAT j) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

class (Ok c p, Eq2 p) => WithEq (a :: FREE c p) Source Comments #

Instances

Instances details
(Ok c p, Eq2 p) => WithEq (a :: FREE c p) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

class Show2 p => WithShow (a :: FREE c p) Source Comments #

Instances

Instances details
Show2 p => WithShow (a :: FREE c p) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

showPostComp :: forall {j} {cs :: [Kind -> Constraint]} {p1 :: CAT j} p2 (a :: FREE cs p1) (b :: FREE cs p1). (Show p2, WithShow a) => Int -> p2 -> Free a b -> ShowS Source Comments #

class IsFreeOb (a :: FREE cs p) where Source Comments #

Associated Types

type Lower (f :: j +-> k) (a :: FREE cs p) :: k Source Comments #

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f a) => r) -> r Source Comments #

Instances

Instances details
Elem Monoidal cs => IsFreeOb (UnitF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (UnitF :: FREE cs p)) => r) -> r Source Comments #

Elem HasInitialObject cs => IsFreeOb (InitF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Initial

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (InitF :: FREE cs p)) => r) -> r Source Comments #

Elem HasTerminalObject cs => IsFreeOb (TermF :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (TermF :: FREE cs p)) => r) -> r Source Comments #

(Ob a, Ob b, Elem Monoidal cs) => IsFreeOb (a **! b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a **! b)) => r) -> r Source Comments #

(Ob a, Ob b, Elem HasBinaryCoproducts cs) => IsFreeOb (a + b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryCoproduct

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a + b)) => r) -> r Source Comments #

(Ob a, Ob b, Elem HasBinaryProducts cs) => IsFreeOb (a *! b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a *! b)) => r) -> r Source Comments #

(Ob a, Ob b, Elem Closed cs, Elem Monoidal cs) => IsFreeOb (a --> b :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Object.Exponential

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f (a --> b)) => r) -> r Source Comments #

(Ob a, Typeable a) => IsFreeOb ('EMB a :: FREE cs p) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

Methods

withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f ('EMB a :: FREE cs p)) => r) -> r Source Comments #

class ((Ok cs p, Eq2 p) => Eq2 str, Ok cs p => Typeable str, Show2 p => Show2 str) => CanEqShow (str :: CAT (FREE cs p)) Source Comments #

Instances

Instances details
((Ok cs p, Eq2 p) => Eq2 str, Ok cs p => Typeable str, Show2 p => Show2 str) => CanEqShow (str :: FREE cs p -> FREE cs p -> Type) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Free

class (Typeable c, CanEqShow (Struct c :: CAT (FREE cs p)), Elem c cs) => HasStructure (cs :: [Kind -> Constraint]) (p :: CAT j) (c :: Kind -> Constraint) where Source Comments #

Associated Types

data Struct (c :: Kind -> Constraint) :: CAT (FREE cs p) Source Comments #

Methods

foldStructure :: forall {k} (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: FREE cs p) (y :: FREE cs p). (x ~> y) -> Lower f x ~> Lower f y) -> Struct c a b -> Lower f a ~> Lower f b Source Comments #

Instances

Instances details
Elem Monoidal cs => HasStructure cs (p :: CAT j) Monoidal Source Comments # 
Instance details

Defined in Proarrow.Category.Monoidal

Associated Types

data Struct Monoidal (i :: FREE cs p) (o :: FREE cs p) 
Instance details

Defined in Proarrow.Category.Monoidal

data Struct Monoidal (i :: FREE cs p) (o :: FREE cs p) where

Methods

foldStructure :: forall {k} (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: FREE cs p) (y :: FREE cs p). (x ~> y) -> Lower f x ~> Lower f y) -> Struct Monoidal a b -> Lower f a ~> Lower f b Source Comments #

Elem HasBinaryCoproducts cs => HasStructure cs (p :: CAT j) HasBinaryCoproducts Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryCoproduct

Associated Types

data Struct HasBinaryCoproducts (i :: FREE cs p) (o :: FREE cs p) 
Instance details

Defined in Proarrow.Object.BinaryCoproduct

data Struct HasBinaryCoproducts (i :: FREE cs p) (o :: FREE cs p) where

Methods

foldStructure :: forall {k} (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: FREE cs p) (y :: FREE cs p). (x ~> y) -> Lower f x ~> Lower f y) -> Struct HasBinaryCoproducts a b -> Lower f a ~> Lower f b Source Comments #

Elem HasBinaryProducts cs => HasStructure cs (p :: CAT j) HasBinaryProducts Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

Associated Types

data Struct HasBinaryProducts (i :: FREE cs p) (o :: FREE cs p) 
Instance details

Defined in Proarrow.Object.BinaryProduct

data Struct HasBinaryProducts (i :: FREE cs p) (o :: FREE cs p) where

Methods

foldStructure :: forall {k} (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: FREE cs p) (y :: FREE cs p). (x ~> y) -> Lower f x ~> Lower f y) -> Struct HasBinaryProducts a b -> Lower f a ~> Lower f b Source Comments #

(Elem Closed cs, Elem Monoidal cs) => HasStructure cs (p :: CAT j) Closed Source Comments # 
Instance details

Defined in Proarrow.Object.Exponential

Associated Types

data Struct Closed (a :: FREE cs p) (b :: FREE cs p) 
Instance details

Defined in Proarrow.Object.Exponential

data Struct Closed (a :: FREE cs p) (b :: FREE cs p) where

Methods

foldStructure :: forall {k} (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: FREE cs p) (y :: FREE cs p). (x ~> y) -> Lower f x ~> Lower f y) -> Struct Closed a b -> Lower f a ~> Lower f b Source Comments #

Elem HasInitialObject cs => HasStructure cs (p :: CAT j) HasInitialObject Source Comments # 
Instance details

Defined in Proarrow.Object.Initial

Associated Types

data Struct HasInitialObject (a :: FREE cs p) (b :: FREE cs p) 
Instance details

Defined in Proarrow.Object.Initial

data Struct HasInitialObject (a :: FREE cs p) (b :: FREE cs p) where

Methods

foldStructure :: forall {k} (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: FREE cs p) (y :: FREE cs p). (x ~> y) -> Lower f x ~> Lower f y) -> Struct HasInitialObject a b -> Lower f a ~> Lower f b Source Comments #

Elem HasTerminalObject cs => HasStructure cs (p :: CAT j) HasTerminalObject Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

Associated Types

data Struct HasTerminalObject (a :: FREE cs p) (b :: FREE cs p) 
Instance details

Defined in Proarrow.Object.Terminal

data Struct HasTerminalObject (a :: FREE cs p) (b :: FREE cs p) where

Methods

foldStructure :: forall {k} (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: FREE cs p) (y :: FREE cs p). (x ~> y) -> Lower f x ~> Lower f y) -> Struct HasTerminalObject a b -> Lower f a ~> Lower f b Source Comments #

fold :: forall {j} {k} {p} (cs :: [Kind -> Constraint]) (f :: j +-> k) (a :: FREE cs p) (b :: FREE cs p). (All cs k, Representable f) => (forall (x :: j) (y :: j). p x y -> (f % x) ~> (f % y)) -> (a ~> b) -> Lower f a ~> Lower f b Source Comments #

retract :: forall {j} {k} (cs :: [Kind -> Constraint]) (f :: j +-> k) (a :: FREE cs (InitialProfunctor :: j -> j -> Type)) (b :: FREE cs (InitialProfunctor :: j -> j -> Type)). (All cs k, Representable f) => (a ~> b) -> Lower f a ~> Lower f b Source Comments #