gasp-1.4.0.0: A framework of algebraic classes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Algebra.Category.Op

Documentation

newtype Op k a b Source #

Constructors

Op 

Fields

Instances

Instances details
(con ~ Obj k2, Con' x con, UnCon r con, UnCon l con, con i, Autonomous x i r l k2, Braided x i k2) => Autonomous (x :: k1 -> k1 -> k1) (i :: k1) (l :: k1 -> k1) (r :: k1 -> k1) (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

turn :: forall (a :: k). Obj (Op k2) a => Op k2 i (x (l a) a) Source #

turn' :: forall (a :: k). Obj (Op k2) a => Op k2 (x a (r a)) i Source #

(con ~ Obj k2, Con' x con, UnCon d con, con i, Compact x i d k2, Braided x i k2) => Compact (x :: k1 -> k1 -> k1) (i :: k1) (d :: k1 -> k1) (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Braided x i k2 => Braided (x :: k1 -> k1 -> k1) (i :: k1) (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

swap :: forall (a :: k) (b :: k). (Obj (Op k2) a, Obj (Op k2) b) => Op k2 (x a b) (x b a) Source #

swap_ :: forall (a :: k) (b :: k). (Obj (Op k2) a, Obj (Op k2) b) => Op k2 (x a b) (x b a) Source #

CoCartesian x i k2 => Cartesian (x :: k1 -> k1 -> k1) (i :: k1) (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

exl :: forall (a :: k) (b :: k). O2 (Op k2) a b => Op k2 (x a b) a Source #

exr :: forall (a :: k) (b :: k). O2 (Op k2) a b => Op k2 (x a b) b Source #

dis :: forall (a :: k). Obj (Op k2) a => Op k2 a i Source #

dup :: forall (a :: k). Obj (Op k2) a => Op k2 a (x a a) Source #

(▵) :: forall (a :: k) (b :: k) (c :: k). (Obj (Op k2) a, Obj (Op k2) b, Obj (Op k2) c) => Op k2 a b -> Op k2 a c -> Op k2 a (x b c) Source #

Cartesian x i k2 => CoCartesian (x :: k1 -> k1 -> k1) (i :: k1) (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

inl :: forall (a :: k) (b :: k). O2 (Op k2) a b => Op k2 a (x a b) Source #

inr :: forall (a :: k) (b :: k). O2 (Op k2) a b => Op k2 b (x a b) Source #

new :: forall (a :: k). Obj (Op k2) a => Op k2 i a Source #

jam :: forall (a :: k). Obj (Op k2) a => Op k2 (x a a) a Source #

(▿) :: forall (a :: k) (b :: k) (c :: k). (Obj (Op k2) a, Obj (Op k2) b, Obj (Op k2) c) => Op k2 b a -> Op k2 c a -> Op k2 (x b c) a Source #

Monoidal x i k2 => Monoidal (x :: k1 -> k1 -> k1) (i :: k1) (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

(⊗) :: forall (a :: k) (b :: k) (c :: k) (d :: k). (Obj (Op k2) a, Obj (Op k2) b, Obj (Op k2) c, Obj (Op k2) d) => Op k2 a b -> Op k2 c d -> Op k2 (x a c) (x b d) Source #

assoc :: forall (a :: k) (b :: k) (c :: k). (Obj (Op k2) a, Obj (Op k2) b, Obj (Op k2) c) => Op k2 (x (x a b) c) (x a (x b c)) Source #

assoc_ :: forall (a :: k) (b :: k) (c :: k). (Obj (Op k2) a, Obj (Op k2) b, Obj (Op k2) c) => Op k2 (x a (x b c)) (x (x a b) c) Source #

unitorR :: forall (a :: k). (Obj (Op k2) a, Obj (Op k2) i) => Op k2 a (x a i) Source #

unitorR_ :: forall (a :: k). (Obj (Op k2) a, Obj (Op k2) i) => Op k2 (x a i) a Source #

unitorL :: forall (a :: k). (Obj (Op k2) a, Obj (Op k2) i) => Op k2 a (x i a) Source #

unitorL_ :: forall (a :: k). (Obj (Op k2) a, Obj (Op k2) i) => Op k2 (x i a) a Source #

Symmetric x i k2 => Symmetric (x :: k1 -> k1 -> k1) (i :: k1) (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Category k2 => Category (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

Associated Types

type Obj (Op k2) :: k -> Constraint Source #

Methods

(.) :: forall (a :: k) (b :: k) (c :: k). (Obj (Op k2) a, Obj (Op k2) b, Obj (Op k2) c) => Op k2 b c -> Op k2 a b -> Op k2 a c Source #

id :: forall (a :: k). Obj (Op k2) a => Op k2 a a Source #

Arbitrary (f b a) => Arbitrary (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

arbitrary :: Gen (Op f a b) #

shrink :: Op f a b -> [Op f a b] #

Show (f b a) => Show (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

showsPrec :: Int -> Op f a b -> ShowS #

show :: Op f a b -> String #

showList :: [Op f a b] -> ShowS #

Additive (f b a) => Additive (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

(+) :: Op f a b -> Op f a b -> Op f a b Source #

zero :: Op f a b Source #

times :: Natural -> Op f a b -> Op f a b Source #

Group (f b a) => Group (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

(-) :: Op f a b -> Op f a b -> Op f a b Source #

subtract :: Op f a b -> Op f a b -> Op f a b Source #

negate :: Op f a b -> Op f a b Source #

mult :: Integer -> Op f a b -> Op f a b Source #

TestEqual (f b a) => TestEqual (Op f a b) Source # 
Instance details

Defined in Algebra.Category.Op

Methods

(=.=) :: Op f a b -> Op f a b -> Property Source #

type Obj (Op k2 :: k1 -> k1 -> Type) Source # 
Instance details

Defined in Algebra.Category.Op

type Obj (Op k2 :: k1 -> k1 -> Type) = Obj k2