Safe Haskell | None |
---|---|
Language | GHC2024 |
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 #
class (forall k. FromAll cs c k) => Elem (c :: Kind -> Constraint) (cs :: [Kind -> Constraint]) Source Comments #
newtype FREE (cs :: [Kind -> Constraint]) (p :: CAT j) Source Comments #
Constructors
EMB j |
Instances
Elem Monoidal cs => IsFreeOb (UnitF :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Category.Monoidal | |||||
Elem HasInitialObject cs => IsFreeOb (InitF :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.Initial | |||||
Elem HasTerminalObject cs => IsFreeOb (TermF :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.Terminal | |||||
(Ob a, Ob b, Elem Monoidal cs) => IsFreeOb (a **! b :: FREE cs p) Source Comments # | |||||
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 # | |||||
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 # | |||||
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 # | |||||
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 # | |||||
Defined in Proarrow.Category.Monoidal Associated Types
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 # | |||||
Defined in Proarrow.Category.Instance.Free | |||||
(Ok cs p, Elem HasBinaryCoproducts cs) => HasBinaryCoproducts (FREE cs p) Source Comments # | |||||
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 # | |||||
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 # | |||||
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 # | |||||
Defined in Proarrow.Object.Initial Associated Types
| |||||
(Ok cs p, Elem HasTerminalObject cs) => HasTerminalObject (FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.Terminal Associated Types
| |||||
Ok cs p => Promonad (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # | |||||
(Ok cs p, Elem Monoidal cs) => MonoidalProfunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # | |||||
Ok cs p => Profunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # | |||||
Defined in Proarrow.Category.Instance.Free | |||||
type Lower (f :: j +-> k) (UnitF :: FREE cs p) Source Comments # | |||||
type Lower (f :: j +-> k) (InitF :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.Initial | |||||
type Lower (f :: j +-> k) (TermF :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.Terminal | |||||
type Lower (f :: j +-> k) (a **! b :: FREE cs p) Source Comments # | |||||
type Lower (f :: j +-> k) (a + b :: FREE cs p) Source Comments # | |||||
type Lower (f :: j +-> k) (a *! b :: FREE cs p) Source Comments # | |||||
type Lower (f :: j +-> k) (a --> b :: FREE cs p) Source Comments # | |||||
type UN ('EMB :: j -> FREE cs p) ('EMB a :: FREE cs p) Source Comments # | |||||
type Unit Source Comments # | |||||
Defined in Proarrow.Category.Monoidal | |||||
type (~>) Source Comments # | |||||
type InitialObject Source Comments # | |||||
Defined in Proarrow.Object.Initial | |||||
type TerminalObject Source Comments # | |||||
Defined in Proarrow.Object.Terminal | |||||
type Ob (a :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Category.Instance.Free | |||||
type (a :: FREE cs p) ** (b :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Category.Monoidal | |||||
type (a :: FREE cs p) || (b :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.BinaryCoproduct | |||||
type (a :: FREE cs p) && (b :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.BinaryProduct | |||||
type (a :: FREE cs p) ~~> (b :: FREE cs p) Source Comments # | |||||
Defined in Proarrow.Object.Exponential |
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
Ok cs p => Promonad (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # | |
(Ok cs p, Elem Monoidal cs) => MonoidalProfunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # | |
Ok cs p => Profunctor (Free :: FREE cs p -> FREE cs p -> Type) Source Comments # | |
Defined in Proarrow.Category.Instance.Free | |
WithShow a => Show (Free a b) Source Comments # | |
WithEq a => Eq (Free a b) Source 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 (Typeable p, Typeable cs, Typeable j, All cs (FREE cs p)) => Ok (cs :: [Kind -> Constraint]) (p :: CAT j) Source Comments #
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 #
Methods
withLowerOb :: forall {k} (f :: j +-> k) r. (Representable f, All cs k) => (Ob (Lower f a) => r) -> r Source Comments #
Instances
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 #
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 #
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
Elem Monoidal cs => HasStructure cs (p :: CAT j) Monoidal Source Comments # | |||||
Defined in Proarrow.Category.Monoidal Associated Types
| |||||
Elem HasBinaryCoproducts cs => HasStructure cs (p :: CAT j) HasBinaryCoproducts Source Comments # | |||||
Defined in Proarrow.Object.BinaryCoproduct Associated Types
| |||||
Elem HasBinaryProducts cs => HasStructure cs (p :: CAT j) HasBinaryProducts Source Comments # | |||||
Defined in Proarrow.Object.BinaryProduct Associated Types
| |||||
(Elem Closed cs, Elem Monoidal cs) => HasStructure cs (p :: CAT j) Closed Source Comments # | |||||
Defined in Proarrow.Object.Exponential Associated Types
| |||||
Elem HasInitialObject cs => HasStructure cs (p :: CAT j) HasInitialObject Source Comments # | |||||
Defined in Proarrow.Object.Initial Associated Types
| |||||
Elem HasTerminalObject cs => HasStructure cs (p :: CAT j) HasTerminalObject Source Comments # | |||||
Defined in Proarrow.Object.Terminal Associated Types
|
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 #