proarrow
Safe HaskellNone
LanguageGHC2024

Proarrow.Category.Instance.Constraint

Documentation

newtype CONSTRAINT Source Comments #

Constructors

CNSTRNT Constraint 

Instances

Instances details
Monoidal CONSTRAINT Source Comments #

Products as monoidal structure.

Instance details

Defined in Proarrow.Category.Instance.Constraint

Associated Types

type Unit 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (a :: CONSTRAINT) ** (b :: CONSTRAINT) 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (a :: CONSTRAINT) ** (b :: CONSTRAINT) = a && b

Methods

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

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

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

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

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

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

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

SymMonoidal CONSTRAINT Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

swap :: forall (a :: CONSTRAINT) (b :: CONSTRAINT). (Ob a, Ob b) => (a ** b) ~> (b ** a) Source Comments #

CategoryOf CONSTRAINT Source Comments #

The category of type class constraints. An arrow from constraint a to constraint b | means that a implies b, i.e. if a holds then b holds.

Instance details

Defined in Proarrow.Category.Instance.Constraint

Associated Types

type (~>) 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (~>) = (:-)
type Ob (a :: CONSTRAINT) 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type Ob (a :: CONSTRAINT) = Is 'CNSTRNT a
CopyDiscard CONSTRAINT Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

copy :: forall (a :: CONSTRAINT). Ob a => a ~> (a ** a) Source Comments #

discard :: forall (a :: CONSTRAINT). Ob a => a ~> (Unit :: CONSTRAINT) Source Comments #

HasBinaryProducts CONSTRAINT Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Associated Types

type ('CNSTRNT l :: CONSTRAINT) && ('CNSTRNT r :: CONSTRAINT) 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type ('CNSTRNT l :: CONSTRAINT) && ('CNSTRNT r :: CONSTRAINT) = 'CNSTRNT (l, r)

Methods

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

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

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

(&&&) :: forall (a :: CONSTRAINT) (x :: CONSTRAINT) (y :: CONSTRAINT). (a ~> x) -> (a ~> y) -> a ~> (x && y) Source Comments #

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

Closed CONSTRAINT Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Associated Types

type (a :: CONSTRAINT) ~~> (b :: CONSTRAINT) 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (a :: CONSTRAINT) ~~> (b :: CONSTRAINT) = 'CNSTRNT (UN 'CNSTRNT a :=> UN 'CNSTRNT b)

Methods

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

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

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

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

HasTerminalObject CONSTRAINT Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Associated Types

type TerminalObject 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

terminate :: forall (a :: CONSTRAINT). Ob a => a ~> (TerminalObject :: CONSTRAINT) Source Comments #

Promonad (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

id :: forall (a :: CONSTRAINT). Ob a => a :- a Source Comments #

(.) :: forall (b :: CONSTRAINT) (c :: CONSTRAINT) (a :: CONSTRAINT). (b :- c) -> (a :- b) -> a :- c Source Comments #

ThinProfunctor (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Associated Types

type HasArrow (:-) (a :: CONSTRAINT) (b :: CONSTRAINT) 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

arr :: forall (a :: CONSTRAINT) (b :: CONSTRAINT). (Ob a, Ob b, HasArrow (:-) a b) => a :- b Source Comments #

withArr :: forall (a :: CONSTRAINT) (b :: CONSTRAINT) r. (a :- b) -> (HasArrow (:-) a b => r) -> r Source Comments #

MonoidalProfunctor (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

par0 :: (Unit :: CONSTRAINT) :- (Unit :: CONSTRAINT) Source Comments #

par :: forall (x1 :: CONSTRAINT) (x2 :: CONSTRAINT) (y1 :: CONSTRAINT) (y2 :: CONSTRAINT). (x1 :- x2) -> (y1 :- y2) -> (x1 ** y1) :- (x2 ** y2) Source Comments #

Profunctor (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

dimap :: forall (c :: CONSTRAINT) (a :: CONSTRAINT) (b :: CONSTRAINT) (d :: CONSTRAINT). (c ~> a) -> (b ~> d) -> (a :- b) -> c :- d Source Comments #

(\\) :: forall (a :: CONSTRAINT) (b :: CONSTRAINT) r. ((Ob a, Ob b) => r) -> (a :- b) -> r Source Comments #

ThinProfunctor p => EnrichedProfunctor CONSTRAINT (p :: j +-> k) Source Comments # 
Instance details

Defined in Proarrow.Category.Enriched

Methods

withProObj :: forall (a :: k) (b :: j) r. (Ob a, Ob b) => (Ob (ProObj CONSTRAINT p a b) => r) -> r Source Comments #

underlying :: forall (a :: k) (b :: j). p a b -> (Unit :: CONSTRAINT) ~> ProObj CONSTRAINT p a b Source Comments #

enriched :: forall (a :: k) (b :: j). (Ob a, Ob b) => ((Unit :: CONSTRAINT) ~> ProObj CONSTRAINT p a b) -> p a b Source Comments #

rmap :: forall (a :: k) (b :: j) (c :: j). (Ob a, Ob b, Ob c) => (HomObj CONSTRAINT b c ** ProObj CONSTRAINT p a b) ~> ProObj CONSTRAINT p a c Source Comments #

lmap :: forall (a :: k) (b :: j) (c :: k). (Ob a, Ob b, Ob c) => (HomObj CONSTRAINT c a ** ProObj CONSTRAINT p a b) ~> ProObj CONSTRAINT p c b Source Comments #

Comonoid ('CNSTRNT a :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Monoid ('CNSTRNT ()) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type Unit Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (~>) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (~>) = (:-)
type TerminalObject Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type Ob (a :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type Ob (a :: CONSTRAINT) = Is 'CNSTRNT a
type (a :: CONSTRAINT) ** (b :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (a :: CONSTRAINT) ** (b :: CONSTRAINT) = a && b
type (a :: CONSTRAINT) ~~> (b :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type (a :: CONSTRAINT) ~~> (b :: CONSTRAINT) = 'CNSTRNT (UN 'CNSTRNT a :=> UN 'CNSTRNT b)
type HasArrow (:-) (a :: CONSTRAINT) (b :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type ProObj CONSTRAINT (p :: j +-> k) (a :: k) (b :: j) Source Comments # 
Instance details

Defined in Proarrow.Category.Enriched

type ProObj CONSTRAINT (p :: j +-> k) (a :: k) (b :: j) = 'CNSTRNT (HasArrow p a b)
type UN 'CNSTRNT ('CNSTRNT a :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type UN 'CNSTRNT ('CNSTRNT a :: CONSTRAINT) = a
type ('CNSTRNT l :: CONSTRAINT) && ('CNSTRNT r :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

type ('CNSTRNT l :: CONSTRAINT) && ('CNSTRNT r :: CONSTRAINT) = 'CNSTRNT (l, r)

data (a :: CONSTRAINT) :- (b :: CONSTRAINT) where Source Comments #

Constructors

Entails 

Fields

Instances

Instances details
Promonad (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

id :: forall (a :: CONSTRAINT). Ob a => a :- a Source Comments #

(.) :: forall (b :: CONSTRAINT) (c :: CONSTRAINT) (a :: CONSTRAINT). (b :- c) -> (a :- b) -> a :- c Source Comments #

ThinProfunctor (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Associated Types

type HasArrow (:-) (a :: CONSTRAINT) (b :: CONSTRAINT) 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

arr :: forall (a :: CONSTRAINT) (b :: CONSTRAINT). (Ob a, Ob b, HasArrow (:-) a b) => a :- b Source Comments #

withArr :: forall (a :: CONSTRAINT) (b :: CONSTRAINT) r. (a :- b) -> (HasArrow (:-) a b => r) -> r Source Comments #

MonoidalProfunctor (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

par0 :: (Unit :: CONSTRAINT) :- (Unit :: CONSTRAINT) Source Comments #

par :: forall (x1 :: CONSTRAINT) (x2 :: CONSTRAINT) (y1 :: CONSTRAINT) (y2 :: CONSTRAINT). (x1 :- x2) -> (y1 :- y2) -> (x1 ** y1) :- (x2 ** y2) Source Comments #

Profunctor (:-) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

Methods

dimap :: forall (c :: CONSTRAINT) (a :: CONSTRAINT) (b :: CONSTRAINT) (d :: CONSTRAINT). (c ~> a) -> (b ~> d) -> (a :- b) -> c :- d Source Comments #

(\\) :: forall (a :: CONSTRAINT) (b :: CONSTRAINT) r. ((Ob a, Ob b) => r) -> (a :- b) -> r Source Comments #

type HasArrow (:-) (a :: CONSTRAINT) (b :: CONSTRAINT) Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

class b :=> c where Source Comments #

Instances

Instances details
(b => c) => b :=> c Source Comments # 
Instance details

Defined in Proarrow.Category.Instance.Constraint

reifyExp :: ('CNSTRNT b :- 'CNSTRNT c) -> (b :=> c => r) -> r Source Comments #