proarrow
Safe HaskellNone
LanguageGHC2024

Proarrow.Tools.Laws

Documentation

data AssertEq (cs :: [Kind -> Constraint]) where Source Comments #

Constructors

(:=:) :: forall {cs :: [Kind -> Constraint]} (a :: FREE cs (Var cs)) (b :: FREE cs (Var cs)). (Elem a (EqTypes cs), Elem b (EqTypes cs)) => Free a b -> Free a b -> AssertEq cs infix 0 

Instances

Instances details
Show2 (Var cs) => Show (AssertEq cs) Source Comments # 
Instance details

Defined in Proarrow.Tools.Laws

data family Var (cs :: [Kind -> Constraint]) (a :: Symbol) (b :: Symbol) Source Comments #

Instances

Instances details
Show (Var '[HasBinaryProducts] a b) Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

Show (Var '[HasTerminalObject] a b) Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

data Var '[HasBinaryProducts] a b Source Comments # 
Instance details

Defined in Proarrow.Object.BinaryProduct

data Var '[HasBinaryProducts] a b where
data Var '[HasTerminalObject] a b Source Comments # 
Instance details

Defined in Proarrow.Object.Terminal

data Var '[HasTerminalObject] a b where

class Laws (cs :: [Kind -> Constraint]) where Source Comments #

Associated Types

type EqTypes (cs :: [Kind -> Constraint]) :: [FREE cs (Var cs)] Source Comments #

Methods

laws :: [AssertEq cs] Source Comments #

data Place (as :: [k]) (a :: k) where Source Comments #

Constructors

Here :: forall {k} (a :: k) (as1 :: [k]). Place (a ': as1) a 
There :: forall {k} (a :: k) (as1 :: [k]) (a1 :: k). Elem a as1 => Place (a1 ': as1) a 

class Elem (c :: a) (cs :: [a]) where Source Comments #

Methods

place :: Place cs c Source Comments #

Instances

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

Defined in Proarrow.Tools.Laws

Methods

place :: Place (c ': cs) c Source Comments #

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

Defined in Proarrow.Tools.Laws

Methods

place :: Place (d ': cs) c Source Comments #

data Sym (a :: Symbol) (b :: Symbol) where Source Comments #

Constructors

Sym :: forall (a :: Symbol) (b :: Symbol). (KnownSymbol a, KnownSymbol b) => (a :~: b) -> Sym a b 

Instances

Instances details
Promonad Sym Source Comments # 
Instance details

Defined in Proarrow.Tools.Laws

Methods

id :: forall (a :: Symbol). Ob a => Sym a a Source Comments #

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

Profunctor Sym Source Comments # 
Instance details

Defined in Proarrow.Tools.Laws

Methods

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

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

Orphan instances

CategoryOf Symbol Source Comments # 
Instance details

Associated Types

type (~>) 
Instance details

Defined in Proarrow.Tools.Laws

type (~>) = Sym
type Ob (a :: Symbol) 
Instance details

Defined in Proarrow.Tools.Laws

type Ob (a :: Symbol) = KnownSymbol a